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

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

.f90 <-> .F90 depending on cpp key use

  • Property svn:keywords set to Id
File size: 61.3 KB
Line 
1#include "conf_gcm.f90"
2
3!
4! $Id: 1DUTILS.h 5268 2024-10-23 17:02:39Z 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      include "netcdf.inc"
681
682!   Arguments:
683!   ----------
684      CHARACTER*(*) fichnom
685!Al1 plev tronque pour .nc mais plev(klev+1):=0
686      real :: plev(klon,klev+1),play (klon,klev),phi(klon,klev)
687      real :: presnivs(klon,klev)
688      real :: ucov(klon,klev),vcov(klon,klev),temp(klon,klev)
689      real :: q(klon,klev,nqtot),omega2(klon,klev)
690!      real :: ug(klev),vg(klev),fcoriolis
691      real :: phis(klon) 
692
693!   Variables locales pour NetCDF:
694!   ------------------------------
695      INTEGER iq
696      INTEGER length
697      PARAMETER (length = 100)
698      REAL tab_cntrl(length) ! tableau des parametres du run
699      character*4 nmq(nqtot)
700      character*12 modname
701      character*80 abort_message
702      LOGICAL found
703
704      modname = 'dyn1deta0 : '
705!!      nmq(1)="vap"
706!!      nmq(2)="cond"
707!!      do iq=3,nqtot
708!!        write(nmq(iq),'("tra",i1)') iq-2
709!!      enddo
710      DO iq = 1,nqtot
711        nmq(iq) = trim(tracers(iq)%name)
712      ENDDO
713      print*,'in dyn1deta0 ',fichnom,klon,klev,nqtot
714      CALL open_startphy(fichnom)
715      print*,'after open startphy ',fichnom,nmq
716
717!
718! Lecture des parametres de controle:
719!
720      CALL get_var("controle",tab_cntrl)
721       
722
723      im         = tab_cntrl(1)
724      jm         = tab_cntrl(2)
725      lllm       = tab_cntrl(3)
726      day_ref    = tab_cntrl(4)
727      annee_ref  = tab_cntrl(5)
728!      rad        = tab_cntrl(6)
729!      omeg       = tab_cntrl(7)
730!      g          = tab_cntrl(8)
731!      cpp        = tab_cntrl(9)
732!      kappa      = tab_cntrl(10)
733!      daysec     = tab_cntrl(11)
734!      dtvr       = tab_cntrl(12)
735!      etot0      = tab_cntrl(13)
736!      ptot0      = tab_cntrl(14)
737!      ztot0      = tab_cntrl(15)
738!      stot0      = tab_cntrl(16)
739!      ang0       = tab_cntrl(17)
740!      pa         = tab_cntrl(18)
741!      preff      = tab_cntrl(19)
742!
743!      clon       = tab_cntrl(20)
744!      clat       = tab_cntrl(21)
745!      grossismx  = tab_cntrl(22)
746!      grossismy  = tab_cntrl(23)
747!
748      IF ( tab_cntrl(24).EQ.1. )  THEN
749        fxyhypb  =.true.
750!        dzoomx   = tab_cntrl(25)
751!        dzoomy   = tab_cntrl(26)
752!        taux     = tab_cntrl(28)
753!        tauy     = tab_cntrl(29)
754      ELSE
755        fxyhypb = .false.
756        ysinus  = .false.
757        IF( tab_cntrl(27).EQ.1. ) ysinus =.true. 
758      ENDIF
759
760      day_ini = tab_cntrl(30)
761      itau_dyn = tab_cntrl(31)
762!   .................................................................
763!
764!
765!      PRINT*,'rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa
766!Al1
767       Print*,'day_ref,annee_ref,day_ini,itau_dyn',                         &
768     &              day_ref,annee_ref,day_ini,itau_dyn
769
770!  Lecture des champs
771!
772      CALL get_field("play",play,found)
773      IF (.NOT. found) PRINT*, modname//'Le champ <Play> est absent'
774      CALL get_field("phi",phi,found)
775      IF (.NOT. found) PRINT*, modname//'Le champ <Phi> est absent'
776      CALL get_field("phis",phis,found)
777      IF (.NOT. found) PRINT*, modname//'Le champ <Phis> est absent'
778      CALL get_field("presnivs",presnivs,found)
779      IF (.NOT. found) PRINT*, modname//'Le champ <Presnivs> est absent'
780      CALL get_field("ucov",ucov,found)
781      IF (.NOT. found) PRINT*, modname//'Le champ <ucov> est absent'
782      CALL get_field("vcov",vcov,found)
783      IF (.NOT. found) PRINT*, modname//'Le champ <vcov> est absent'
784      CALL get_field("temp",temp,found)
785      IF (.NOT. found) PRINT*, modname//'Le champ <temp> est absent'
786      CALL get_field("omega2",omega2,found)
787      IF (.NOT. found) PRINT*, modname//'Le champ <omega2> est absent'
788      plev(1,klev+1)=0.
789      CALL get_field("plev",plev(:,1:klev),found)
790      IF (.NOT. found) PRINT*, modname//'Le champ <Plev> est absent'
791
792      Do iq=1,nqtot
793        CALL get_field("q"//nmq(iq),q(:,:,iq),found)
794        IF (.NOT.found)PRINT*, modname//'Le champ <q'//nmq//'> est absent'
795      EndDo
796
797      CALL close_startphy
798      print*,' close startphy',fichnom,play(1,1),play(1,klev),temp(1,klev)
799!
800      RETURN
801      END
802!
803! $Id: dyn1dredem.F 1279 2010/07/29 A Lahellec$
804!
805!
806      SUBROUTINE dyn1dredem(fichnom,plev,play,phi,phis,presnivs,           &
807     &                          ucov,vcov,temp,q,omega2)
808      USE dimphy
809      USE mod_grid_phy_lmdz
810      USE mod_phys_lmdz_para
811      USE phys_state_var_mod
812      USE iostart
813      USE infotrac
814      use control_mod
815      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
816      USE logic_mod, ONLY: fxyhypb, ysinus
817      USE temps_mod, ONLY: annee_ref,day_end,day_ref,itau_dyn,itaufin
818
819      IMPLICIT NONE
820!=======================================================
821! Ecriture du fichier de redemarrage sous format NetCDF
822!=======================================================
823!   Declarations:
824!   -------------
825      include "dimensions.h"
826!!#include "control.h"
827      include "netcdf.inc"
828
829!   Arguments:
830!   ----------
831      CHARACTER*(*) fichnom
832!Al1 plev tronque pour .nc mais plev(klev+1):=0
833      real :: plev(klon,klev),play (klon,klev),phi(klon,klev)
834      real :: presnivs(klon,klev)
835      real :: ucov(klon,klev),vcov(klon,klev),temp(klon,klev)
836      real :: q(klon,klev,nqtot)
837      real :: omega2(klon,klev),rho(klon,klev+1)
838!      real :: ug(klev),vg(klev),fcoriolis
839      real :: phis(klon) 
840
841!   Variables locales pour NetCDF:
842!   ------------------------------
843      INTEGER nid
844      INTEGER ierr
845      INTEGER iq,l
846      INTEGER length
847      PARAMETER (length = 100)
848      REAL tab_cntrl(length) ! tableau des parametres du run
849      character*4 nmq(nqtot)
850      character*20 modname
851      character*80 abort_message
852!
853      INTEGER pass
854
855      CALL open_restartphy(fichnom)
856      print*,'redm1 ',fichnom,klon,klev,nqtot
857!!      nmq(1)="vap"
858!!      nmq(2)="cond"
859!!      nmq(3)="tra1"
860!!      nmq(4)="tra2"
861      DO iq = 1,nqtot
862        nmq(iq) = trim(tracers(iq)%name)
863      ENDDO
864
865!     modname = 'dyn1dredem'
866!     ierr = NF_OPEN(fichnom, NF_WRITE, nid)
867!     IF (ierr .NE. NF_NOERR) THEN
868!        abort_message="Pb. d ouverture "//fichnom
869!        CALL abort_gcm('Modele 1D',abort_message,1)
870!     ENDIF
871
872      DO l=1,length
873       tab_cntrl(l) = 0.
874      ENDDO
875       tab_cntrl(1)  = FLOAT(iim)
876       tab_cntrl(2)  = FLOAT(jjm)
877       tab_cntrl(3)  = FLOAT(llm)
878       tab_cntrl(4)  = FLOAT(day_ref)
879       tab_cntrl(5)  = FLOAT(annee_ref)
880       tab_cntrl(6)  = rad
881       tab_cntrl(7)  = omeg
882       tab_cntrl(8)  = g
883       tab_cntrl(9)  = cpp
884       tab_cntrl(10) = kappa
885       tab_cntrl(11) = daysec
886       tab_cntrl(12) = dtvr
887!       tab_cntrl(13) = etot0
888!       tab_cntrl(14) = ptot0
889!       tab_cntrl(15) = ztot0
890!       tab_cntrl(16) = stot0
891!       tab_cntrl(17) = ang0
892!       tab_cntrl(18) = pa
893!       tab_cntrl(19) = preff
894!
895!    .....    parametres  pour le zoom      ......   
896
897!       tab_cntrl(20)  = clon
898!       tab_cntrl(21)  = clat
899!       tab_cntrl(22)  = grossismx
900!       tab_cntrl(23)  = grossismy
901!
902      IF ( fxyhypb )   THEN
903       tab_cntrl(24) = 1.
904!       tab_cntrl(25) = dzoomx
905!       tab_cntrl(26) = dzoomy
906       tab_cntrl(27) = 0.
907!       tab_cntrl(28) = taux
908!       tab_cntrl(29) = tauy
909      ELSE
910       tab_cntrl(24) = 0.
911!       tab_cntrl(25) = dzoomx
912!       tab_cntrl(26) = dzoomy
913       tab_cntrl(27) = 0.
914       tab_cntrl(28) = 0.
915       tab_cntrl(29) = 0.
916       IF( ysinus )  tab_cntrl(27) = 1.
917      ENDIF
918!Al1 iday_end -> day_end
919       tab_cntrl(30) = FLOAT(day_end)
920       tab_cntrl(31) = FLOAT(itau_dyn + itaufin)
921!
922      DO pass=1,2
923      CALL put_var(pass,"controle","Param. de controle Dyn1D",tab_cntrl)
924!
925
926!  Ecriture/extension de la coordonnee temps
927
928
929!  Ecriture des champs
930!
931      CALL put_field(pass,"plev","p interfaces sauf la nulle",plev)
932      CALL put_field(pass,"play","",play)
933      CALL put_field(pass,"phi","geopotentielle",phi)
934      CALL put_field(pass,"phis","geopotentiell de surface",phis)
935      CALL put_field(pass,"presnivs","",presnivs)
936      CALL put_field(pass,"ucov","",ucov)
937      CALL put_field(pass,"vcov","",vcov)
938      CALL put_field(pass,"temp","",temp)
939      CALL put_field(pass,"omega2","",omega2)
940
941      Do iq=1,nqtot
942        CALL put_field(pass,"q"//nmq(iq),"eau vap ou condens et traceurs",           &
943     &                                                      q(:,:,iq))
944      EndDo
945    IF (pass==1) CALL enddef_restartphy
946    IF (pass==2) CALL close_restartphy
947
948
949      ENDDO
950
951!
952      RETURN
953      END
954      SUBROUTINE gr_fi_dyn(nfield,ngrid,im,jm,pfi,pdyn)
955      IMPLICIT NONE
956!=======================================================================
957!   passage d'un champ de la grille scalaire a la grille physique
958!=======================================================================
959 
960!-----------------------------------------------------------------------
961!   declarations:
962!   -------------
963 
964      INTEGER im,jm,ngrid,nfield
965      REAL pdyn(im,jm,nfield)
966      REAL pfi(ngrid,nfield)
967 
968      INTEGER i,j,ifield,ig
969 
970!-----------------------------------------------------------------------
971!   calcul:
972!   -------
973 
974      DO ifield=1,nfield
975!   traitement des poles
976         DO i=1,im
977            pdyn(i,1,ifield)=pfi(1,ifield)
978            pdyn(i,jm,ifield)=pfi(ngrid,ifield)
979         ENDDO
980 
981!   traitement des point normaux
982         DO j=2,jm-1
983            ig=2+(j-2)*(im-1)
984            CALL SCOPY(im-1,pfi(ig,ifield),1,pdyn(1,j,ifield),1)
985            pdyn(im,j,ifield)=pdyn(1,j,ifield)
986         ENDDO
987      ENDDO
988 
989      RETURN
990      END
991 
992 
993
994      SUBROUTINE abort_gcm(modname, message, ierr)
995 
996      USE IOIPSL
997!
998! Stops the simulation cleanly, closing files and printing various
999! comments
1000!
1001!  Input: modname = name of calling program
1002!         message = stuff to print
1003!         ierr    = severity of situation ( = 0 normal )
1004 
1005      character(len=*) modname
1006      integer ierr
1007      character(len=*) message
1008 
1009      write(*,*) 'in abort_gcm'
1010      call histclo
1011!     call histclo(2)
1012!     call histclo(3)
1013!     call histclo(4)
1014!     call histclo(5)
1015      write(*,*) 'out of histclo'
1016      write(*,*) 'Stopping in ', modname
1017      write(*,*) 'Reason = ',message
1018      call getin_dump
1019!
1020      if (ierr .eq. 0) then
1021        write(*,*) 'Everything is cool'
1022      else
1023        write(*,*) 'Houston, we have a problem ', ierr
1024      endif
1025      STOP
1026      END
1027      REAL FUNCTION fq_sat(kelvin, millibar)
1028!
1029      IMPLICIT none
1030!======================================================================
1031! Autheur(s): Z.X. Li (LMD/CNRS)
1032! Objet: calculer la vapeur d'eau saturante (formule Centre Euro.)
1033!======================================================================
1034! Arguments:
1035! kelvin---input-R: temperature en Kelvin
1036! millibar--input-R: pression en mb
1037!
1038! fq_sat----output-R: vapeur d'eau saturante en kg/kg
1039!======================================================================
1040!
1041      REAL kelvin, millibar
1042!
1043      REAL r2es
1044      PARAMETER (r2es=611.14 *18.0153/28.9644)
1045!
1046      REAL r3les, r3ies, r3es
1047      PARAMETER (R3LES=17.269)
1048      PARAMETER (R3IES=21.875)
1049!
1050      REAL r4les, r4ies, r4es
1051      PARAMETER (R4LES=35.86)
1052      PARAMETER (R4IES=7.66)
1053!
1054      REAL rtt
1055      PARAMETER (rtt=273.16)
1056!
1057      REAL retv
1058      PARAMETER (retv=28.9644/18.0153 - 1.0)
1059!
1060      REAL zqsat
1061      REAL temp, pres
1062!     ------------------------------------------------------------------
1063!
1064!
1065      temp = kelvin
1066      pres = millibar * 100.0
1067!      write(*,*)'kelvin,millibar=',kelvin,millibar
1068!      write(*,*)'temp,pres=',temp,pres
1069!
1070      IF (temp .LE. rtt) THEN
1071         r3es = r3ies
1072         r4es = r4ies
1073      ELSE
1074         r3es = r3les
1075         r4es = r4les
1076      ENDIF
1077!
1078      zqsat=r2es/pres * EXP ( r3es*(temp-rtt) / (temp-r4es) )
1079      zqsat=MIN(0.5,ZQSAT)
1080      zqsat=zqsat/(1.-retv  *zqsat)
1081!
1082      fq_sat = zqsat
1083!
1084      RETURN
1085      END
1086 
1087      SUBROUTINE gr_dyn_fi(nfield,im,jm,ngrid,pdyn,pfi)
1088      IMPLICIT NONE
1089!=======================================================================
1090!   passage d'un champ de la grille scalaire a la grille physique
1091!=======================================================================
1092 
1093!-----------------------------------------------------------------------
1094!   declarations:
1095!   -------------
1096 
1097      INTEGER im,jm,ngrid,nfield
1098      REAL pdyn(im,jm,nfield)
1099      REAL pfi(ngrid,nfield)
1100 
1101      INTEGER j,ifield,ig
1102 
1103!-----------------------------------------------------------------------
1104!   calcul:
1105!   -------
1106 
1107      IF(ngrid.NE.2+(jm-2)*(im-1).AND.ngrid.NE.1)                          &
1108     &    STOP 'probleme de dim'
1109!   traitement des poles
1110      CALL SCOPY(nfield,pdyn,im*jm,pfi,ngrid)
1111      CALL SCOPY(nfield,pdyn(1,jm,1),im*jm,pfi(ngrid,1),ngrid)
1112 
1113!   traitement des point normaux
1114      DO ifield=1,nfield
1115         DO j=2,jm-1
1116            ig=2+(j-2)*(im-1)
1117            CALL SCOPY(im-1,pdyn(1,j,ifield),1,pfi(ig,ifield),1)
1118         ENDDO
1119      ENDDO
1120 
1121      RETURN
1122      END
1123 
1124      SUBROUTINE disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
1125 
1126!    Ancienne version disvert dont on a modifie nom pour utiliser
1127!    le disvert de dyn3d (qui permet d'utiliser grille avec ab,bp imposes)
1128!    (MPL 18092012)
1129!
1130!    Auteur :  P. Le Van .
1131!
1132      IMPLICIT NONE
1133 
1134      include "dimensions.h"
1135      include "paramet.h"
1136!
1137!=======================================================================
1138!
1139!
1140!    s = sigma ** kappa   :  coordonnee  verticale
1141!    dsig(l)            : epaisseur de la couche l ds la coord.  s
1142!    sig(l)             : sigma a l'interface des couches l et l-1
1143!    ds(l)              : distance entre les couches l et l-1 en coord.s
1144!
1145!=======================================================================
1146!
1147      REAL pa,preff
1148      REAL ap(llmp1),bp(llmp1),dpres(llm),nivsigs(llm),nivsig(llmp1)
1149      REAL presnivs(llm)
1150!
1151!   declarations:
1152!   -------------
1153!
1154      REAL sig(llm+1),dsig(llm)
1155!
1156      INTEGER l
1157      REAL snorm
1158      REAL alpha,beta,gama,delta,deltaz,h
1159      INTEGER np,ierr
1160      REAL pi,x
1161 
1162!-----------------------------------------------------------------------
1163!
1164      pi=2.*ASIN(1.)
1165 
1166      OPEN(99,file='sigma.def',status='old',form='formatted',                   &
1167     &   iostat=ierr)
1168 
1169!-----------------------------------------------------------------------
1170!   cas 1 on lit les options dans sigma.def:
1171!   ----------------------------------------
1172 
1173      IF (ierr.eq.0) THEN
1174 
1175      print*,'WARNING!!! on lit les options dans sigma.def'
1176      READ(99,*) deltaz
1177      READ(99,*) h
1178      READ(99,*) beta
1179      READ(99,*) gama
1180      READ(99,*) delta
1181      READ(99,*) np
1182      CLOSE(99)
1183      alpha=deltaz/(llm*h)
1184!
1185 
1186       DO 1  l = 1, llm
1187       dsig(l) = (alpha+(1.-alpha)*exp(-beta*(llm-l)))*                    &
1188     &          ( (tanh(gama*l)/tanh(gama*llm))**np +                      &
1189     &            (1.-l/FLOAT(llm))*delta )
1190   1   CONTINUE
1191 
1192       sig(1)=1.
1193       DO 101 l=1,llm-1
1194          sig(l+1)=sig(l)*(1.-dsig(l))/(1.+dsig(l))
1195101    CONTINUE
1196       sig(llm+1)=0.
1197 
1198       DO 2  l = 1, llm
1199       dsig(l) = sig(l)-sig(l+1)
1200   2   CONTINUE
1201!
1202 
1203      ELSE
1204!-----------------------------------------------------------------------
1205!   cas 2 ancienne discretisation (LMD5...):
1206!   ----------------------------------------
1207 
1208      PRINT*,'WARNING!!! Ancienne discretisation verticale'
1209 
1210      h=7.
1211      snorm  = 0.
1212      DO l = 1, llm
1213         x = 2.*asin(1.) * (FLOAT(l)-0.5) / float(llm+1)
1214         dsig(l) = 1.0 + 7.0 * SIN(x)**2
1215         snorm = snorm + dsig(l)
1216      ENDDO
1217      snorm = 1./snorm
1218      DO l = 1, llm
1219         dsig(l) = dsig(l)*snorm
1220      ENDDO
1221      sig(llm+1) = 0.
1222      DO l = llm, 1, -1
1223         sig(l) = sig(l+1) + dsig(l)
1224      ENDDO
1225 
1226      ENDIF
1227 
1228 
1229      DO l=1,llm
1230        nivsigs(l) = FLOAT(l)
1231      ENDDO
1232 
1233      DO l=1,llmp1
1234        nivsig(l)= FLOAT(l)
1235      ENDDO
1236 
1237!
1238!    ....  Calculs  de ap(l) et de bp(l)  ....
1239!    .........................................
1240!
1241!
1242!   .....  pa et preff sont lus  sur les fichiers start par lectba  .....
1243!
1244 
1245      bp(llmp1) =   0.
1246 
1247      DO l = 1, llm
1248!c
1249!cc    ap(l) = 0.
1250!cc    bp(l) = sig(l)
1251 
1252      bp(l) = EXP( 1. -1./( sig(l)*sig(l)) )
1253      ap(l) = pa * ( sig(l) - bp(l) )
1254!
1255      ENDDO
1256      ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) )
1257 
1258      PRINT *,' BP '
1259      PRINT *,  bp
1260      PRINT *,' AP '
1261      PRINT *,  ap
1262 
1263      DO l = 1, llm
1264       dpres(l) = bp(l) - bp(l+1)
1265       presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
1266      ENDDO
1267 
1268      PRINT *,' PRESNIVS '
1269      PRINT *,presnivs
1270 
1271      RETURN
1272      END
1273
1274!!======================================================================
1275!       SUBROUTINE read_tsurf1d(knon,sst_out)
1276!
1277!! This subroutine specifies the surface temperature to be used in 1D simulations
1278!
1279!      USE dimphy, ONLY : klon
1280!
1281!      INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
1282!      REAL, DIMENSION(klon), INTENT(OUT)   :: sst_out  ! tsurf used to force the single-column model
1283!
1284!       INTEGER :: i
1285!! COMMON defined in lmdz1d.F:
1286!       real ts_cur
1287!       common /sst_forcing/ts_cur
1288
1289!       DO i = 1, knon
1290!        sst_out(i) = ts_cur
1291!       ENDDO
1292!
1293!      END SUBROUTINE read_tsurf1d
1294!
1295!===============================================================
1296      subroutine advect_vert(llm,w,dt,q,plev)
1297!===============================================================
1298!   Schema amont pour l'advection verticale en 1D
1299!   w est la vitesse verticale dp/dt en Pa/s
1300!   Traitement en volumes finis
1301!   d / dt ( zm q ) = delta_z ( omega q )
1302!   d / dt ( zm ) = delta_z ( omega )
1303!   avec zm = delta_z ( p )
1304!   si * designe la valeur au pas de temps t+dt
1305!   zm*(l) q*(l) - zm(l) q(l) = w(l+1) q(l+1) - w(l) q(l)
1306!   zm*(l) -zm(l) = w(l+1) - w(l)
1307!   avec w=omega * dt
1308!---------------------------------------------------------------
1309      implicit none
1310! arguments
1311      integer llm
1312      real w(llm+1),q(llm),plev(llm+1),dt
1313
1314! local
1315      integer l
1316      real zwq(llm+1),zm(llm+1),zw(llm+1)
1317      real qold
1318
1319!---------------------------------------------------------------
1320
1321      do l=1,llm
1322         zw(l)=dt*w(l)
1323         zm(l)=plev(l)-plev(l+1)
1324         zwq(l)=q(l)*zw(l)
1325      enddo
1326      zwq(llm+1)=0.
1327      zw(llm+1)=0.
1328 
1329      do l=1,llm
1330         qold=q(l)
1331         q(l)=(q(l)*zm(l)+zwq(l+1)-zwq(l))/(zm(l)+zw(l+1)-zw(l))
1332         print*,'ADV Q ',zm(l),zw(l),zwq(l),qold,q(l)
1333      enddo
1334
1335 
1336      return
1337      end
1338
1339!===============================================================
1340
1341
1342       SUBROUTINE advect_va(llm,omega,d_t_va,d_q_va,d_u_va,d_v_va,              &
1343     &                q,temp,u,v,play)
1344!itlmd
1345!----------------------------------------------------------------------
1346!   Calcul de l'advection verticale (ascendance et subsidence) de
1347!   temperature et d'humidite. Hypothese : ce qui rentre de l'exterieur
1348!   a les memes caracteristiques que l'air de la colonne 1D (WTG) ou
1349!   sans WTG rajouter une advection horizontale
1350!---------------------------------------------------------------------- 
1351        implicit none
1352#include "YOMCST.h"
1353!        argument
1354        integer llm
1355        real  omega(llm+1),d_t_va(llm), d_q_va(llm,3)
1356        real  d_u_va(llm), d_v_va(llm)
1357        real  q(llm,3),temp(llm)
1358        real  u(llm),v(llm)
1359        real  play(llm)
1360! interne
1361        integer l
1362        real alpha,omgdown,omgup
1363
1364      do l= 1,llm
1365       if(l.eq.1) then
1366!si omgup pour la couche 1, alors tendance nulle
1367        omgdown=max(omega(2),0.0)
1368        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
1369        d_t_va(l)= alpha*(omgdown)-omgdown*(temp(l)-temp(l+1))             &
1370     &       /(play(l)-play(l+1))
1371
1372        d_q_va(l,:)= -omgdown*(q(l,:)-q(l+1,:))/(play(l)-play(l+1))             
1373
1374        d_u_va(l)= -omgdown*(u(l)-u(l+1))/(play(l)-play(l+1))             
1375        d_v_va(l)= -omgdown*(v(l)-v(l+1))/(play(l)-play(l+1))             
1376
1377       
1378       elseif(l.eq.llm) then
1379        omgup=min(omega(l),0.0)
1380        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
1381        d_t_va(l)= alpha*(omgup)-                                          &
1382
1383!bug?     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-plev(l))
1384     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-play(l))
1385        d_q_va(l,:)= -omgup*(q(l-1,:)-q(l,:))/(play(l-1)-play(l))
1386        d_u_va(l)= -omgup*(u(l-1)-u(l))/(play(l-1)-play(l))
1387        d_v_va(l)= -omgup*(v(l-1)-v(l))/(play(l-1)-play(l))
1388       
1389       else
1390        omgup=min(omega(l),0.0)
1391        omgdown=max(omega(l+1),0.0)
1392        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
1393        d_t_va(l)= alpha*(omgup+omgdown)-omgdown*(temp(l)-temp(l+1))       &
1394     &              /(play(l)-play(l+1))-                                  &
1395!bug?     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-plev(l))
1396     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-play(l))
1397!      print*, '  ??? '
1398
1399        d_q_va(l,:)= -omgdown*(q(l,:)-q(l+1,:))                            &
1400     &              /(play(l)-play(l+1))-                                  &
1401     &              omgup*(q(l-1,:)-q(l,:))/(play(l-1)-play(l)) 
1402        d_u_va(l)= -omgdown*(u(l)-u(l+1))                                  &
1403     &              /(play(l)-play(l+1))-                                  &
1404     &              omgup*(u(l-1)-u(l))/(play(l-1)-play(l)) 
1405        d_v_va(l)= -omgdown*(v(l)-v(l+1))                                  &
1406     &              /(play(l)-play(l+1))-                                  &
1407     &              omgup*(v(l-1)-v(l))/(play(l-1)-play(l))
1408       
1409      endif
1410         
1411      enddo
1412!fin itlmd
1413        return
1414        end
1415!       SUBROUTINE lstendH(llm,omega,d_t_va,d_q_va,d_u_va,d_v_va,
1416       SUBROUTINE lstendH(llm,nqtot,omega,d_t_va,d_q_va,                        &
1417     &                q,temp,u,v,play)
1418!itlmd
1419!----------------------------------------------------------------------
1420!   Calcul de l'advection verticale (ascendance et subsidence) de
1421!   temperature et d'humidite. Hypothese : ce qui rentre de l'exterieur
1422!   a les memes caracteristiques que l'air de la colonne 1D (WTG) ou
1423!   sans WTG rajouter une advection horizontale
1424!---------------------------------------------------------------------- 
1425        implicit none
1426#include "YOMCST.h"
1427!        argument
1428        integer llm,nqtot
1429        real  omega(llm+1),d_t_va(llm), d_q_va(llm,nqtot)
1430!        real  d_u_va(llm), d_v_va(llm)
1431        real  q(llm,nqtot),temp(llm)
1432        real  u(llm),v(llm)
1433        real  play(llm)
1434        real cor(llm)
1435!        real dph(llm),dudp(llm),dvdp(llm),dqdp(llm),dtdp(llm)
1436        real dph(llm),dqdp(llm),dtdp(llm)
1437! interne
1438        integer k
1439        real omdn,omup
1440
1441!        dudp=0.
1442!        dvdp=0.
1443        dqdp=0.
1444        dtdp=0.
1445!        d_u_va=0.
1446!        d_v_va=0.
1447
1448      cor(:) = rkappa*temp*(1.+q(:,1)*rv/rd)/(play*(1.+q(:,1)))
1449
1450
1451      do k=2,llm-1
1452
1453       dph  (k-1) = (play()- play(k-1  ))
1454!       dudp (k-1) = (u   ()- u   (k-1  ))/dph(k-1)
1455!       dvdp (k-1) = (v   ()- v   (k-1  ))/dph(k-1)
1456       dqdp (k-1) = (q   (k,1)- q   (k-1,1))/dph(k-1)
1457       dtdp (k-1) = (temp()- temp(k-1  ))/dph(k-1)
1458
1459      enddo
1460
1461!      dudp (  llm  ) = dudp ( llm-1 )
1462!      dvdp (  llm  ) = dvdp ( llm-1 )
1463      dqdp (  llm  ) = dqdp ( llm-1 )
1464      dtdp (  llm  ) = dtdp ( llm-1 )
1465
1466      do k=2,llm-1
1467      omdn=max(0.0,omega(k+1))
1468      omup=min(0.0,omega( k ))
1469
1470!      d_u_va(k)  = -omdn*dudp(k)-omup*dudp(k-1)
1471!      d_v_va(k)  = -omdn*dvdp(k)-omup*dvdp(k-1)
1472      d_q_va(k,1)= -omdn*dqdp(k)-omup*dqdp(k-1)
1473      d_t_va(k)  = -omdn*dtdp(k)-omup*dtdp(k-1)+(omup+omdn)*cor(k)
1474      enddo
1475
1476      omdn=max(0.0,omega( 2 ))
1477      omup=min(0.0,omega(llm))
1478!      d_u_va( 1 )   = -omdn*dudp( 1 )
1479!      d_u_va(llm)   = -omup*dudp(llm)
1480!      d_v_va( 1 )   = -omdn*dvdp( 1 )
1481!      d_v_va(llm)   = -omup*dvdp(llm)
1482      d_q_va( 1 ,1) = -omdn*dqdp( 1 )
1483      d_q_va(llm,1) = -omup*dqdp(llm)
1484      d_t_va( 1 )   = -omdn*dtdp( 1 )+omdn*cor( 1 )
1485      d_t_va(llm)   = -omup*dtdp(llm)!+omup*cor(llm)
1486
1487!      if(abs(rlat(1))>10.) then
1488!     Calculate the tendency due agestrophic motions
1489!      du_age = fcoriolis*(v-vg)
1490!      dv_age = fcoriolis*(ug-u)
1491!      endif
1492
1493!       call writefield_phy('d_t_va',d_t_va,llm)
1494
1495          return
1496         end
1497
1498!======================================================================
1499
1500!  Subroutines for nudging
1501
1502      Subroutine Nudge_RHT_init (paprs,pplay,t,q,t_targ,rh_targ)
1503! ========================================================
1504  USE dimphy
1505
1506  implicit 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!
1525include "YOMCST.h"
1526include "YOETHF.h"
1527!
1528!  ----------------------------------------
1529!  Statement functions
1530include "FCTTRE.h"
1531!  ----------------------------------------
1532!
1533        DO k = 1,klev
1534         DO i = 1,klon
1535           t_targ(i,k) = t(i,k)
1536           IF (t(i,k).LT.RTT) THEN
1537              zx_qs = qsats(t(i,k))/(pplay(i,k))
1538           ELSE
1539              zx_qs = qsatl(t(i,k))/(pplay(i,k))
1540           ENDIF
1541           rh_targ(i,k) = q(i,k)/zx_qs
1542         ENDDO
1543        ENDDO
1544      print *, 't_targ',t_targ
1545      print *, 'rh_targ',rh_targ
1546!
1547!
1548      RETURN
1549      END
1550
1551      Subroutine Nudge_UV_init (paprs,pplay,u,v,u_targ,v_targ)
1552! ========================================================
1553  USE dimphy
1554
1555  implicit none
1556
1557! ========================================================
1558      REAL paprs(klon,klevp1)
1559      REAL pplay(klon,klev)
1560!
1561!      Variables d'etat
1562      REAL u(klon,klev)
1563      REAL v(klon,klev)
1564!
1565!   Profiles cible
1566      REAL u_targ(klon,klev)
1567      REAL v_targ(klon,klev)
1568!
1569   INTEGER k,i
1570!
1571        DO k = 1,klev
1572         DO i = 1,klon
1573           u_targ(i,k) = u(i,k)
1574           v_targ(i,k) = v(i,k)
1575         ENDDO
1576        ENDDO
1577      print *, 'u_targ',u_targ
1578      print *, 'v_targ',v_targ
1579!
1580!
1581      RETURN
1582      END
1583
1584      Subroutine Nudge_RHT (dtime,paprs,pplay,t_targ,rh_targ,t,q,          &
1585     &                      d_t,d_q)
1586! ========================================================
1587  USE dimphy
1588
1589  implicit 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!
1619include "YOMCST.h"
1620include "YOETHF.h"
1621!
1622!  ----------------------------------------
1623!  Statement functions
1624include "FCTTRE.h"
1625!  ----------------------------------------
1626!
1627        print *,'dtime, tau ',dtime,tau
1628        print *, 't_targ',t_targ
1629        print *, 'rh_targ',rh_targ
1630        print *,'temp ',t
1631        print *,'hum ',q
1632!
1633        DO k = 1,klev
1634         DO i = 1,klon
1635           IF (paprs(i,1)-pplay(i,k) .GT. 10000.) THEN
1636            IF (t(i,k).LT.RTT) THEN
1637               zx_qs = qsats(t(i,k))/(pplay(i,k))
1638            ELSE
1639               zx_qs = qsatl(t(i,k))/(pplay(i,k))
1640            ENDIF
1641            rh = q(i,k)/zx_qs
1642!
1643            d_t(i,k) = d_t(i,k) + 1./tau*(t_targ(i,k)-t(i,k))
1644            d_rh = 1./tau*(rh_targ(i,k)-rh)
1645!
1646            tnew = t(i,k)+d_t(i,k)*dtime
1647!jyg<
1648!   Formule pour q :
1649!                         d_q = (1/tau) [rh_targ*qsat(T_new) - q] 
1650!
1651!  Cette formule remplace d_q = (1/tau) [rh_targ - rh] qsat(T_new)
1652!   qui n'etait pas correcte.
1653!
1654            IF (tnew.LT.RTT) THEN
1655               zx_qs = qsats(tnew)/(pplay(i,k))
1656            ELSE
1657               zx_qs = qsatl(tnew)/(pplay(i,k))
1658            ENDIF
1659!!            d_q(i,k) = d_q(i,k) + d_rh*zx_qs
1660            d_q(i,k) = d_q(i,k) + (1./tau)*(rh_targ(i,k)*zx_qs - q(i,k))
1661            rhnew = (q(i,k)+d_q(i,k)*dtime)/zx_qs
1662!
1663            print *,' k,d_t,rh,d_rh,rhnew,d_q ',    &
1664                      k,d_t(i,k),rh,d_rh,rhnew,d_q(i,k)
1665           ENDIF
1666!
1667         ENDDO
1668        ENDDO
1669!
1670      RETURN
1671      END
1672
1673      Subroutine Nudge_UV (dtime,paprs,pplay,u_targ,v_targ,u,v,          &
1674     &                      d_u,d_v)
1675! ========================================================
1676  USE dimphy
1677
1678  implicit none
1679
1680! ========================================================
1681      REAL dtime
1682      REAL paprs(klon,klevp1)
1683      REAL pplay(klon,klev)
1684!
1685!      Variables d'etat
1686      REAL u(klon,klev)
1687      REAL v(klon,klev)
1688!
1689! Tendances
1690      REAL d_u(klon,klev)
1691      REAL d_v(klon,klev)
1692!
1693!   Profiles cible
1694      REAL u_targ(klon,klev)
1695      REAL v_targ(klon,klev)
1696!
1697!   Temps de relaxation
1698      REAL tau
1699!c      DATA tau /3600./
1700!      DATA tau /5400./
1701       DATA tau /43200./
1702!
1703   INTEGER k,i
1704
1705!
1706        !print *,'dtime, tau ',dtime,tau
1707        !print *, 'u_targ',u_targ
1708        !print *, 'v_targ',v_targ
1709        !print *,'zonal velocity ',u
1710        !print *,'meridional velocity ',v
1711        DO k = 1,klev
1712         DO i = 1,klon
1713!CR: nudging everywhere
1714!           IF (paprs(i,1)-pplay(i,k) .GT. 10000.) THEN
1715!
1716            d_u(i,k) = d_u(i,k) + 1./tau*(u_targ(i,k)-u(i,k))
1717            d_v(i,k) = d_v(i,k) + 1./tau*(v_targ(i,k)-v(i,k))
1718!
1719!           print *,' k,u,d_u,v,d_v ',    &
1720!                     k,u(i,k),d_u(i,k),v(i,k),d_v(i,k)
1721!           ENDIF
1722!
1723         ENDDO
1724        ENDDO
1725!
1726      RETURN
1727      END
1728
1729!=====================================================================
1730       SUBROUTINE interp2_case_vertical(play,nlev_cas,plev_prof_cas                                    &
1731     &         ,t_prof_cas,th_prof_cas,thv_prof_cas,thl_prof_cas                                       &
1732     &         ,qv_prof_cas,ql_prof_cas,qi_prof_cas,u_prof_cas,v_prof_cas                              &
1733     &         ,ug_prof_cas,vg_prof_cas,vitw_prof_cas,omega_prof_cas                                   &
1734     &         ,du_prof_cas,hu_prof_cas,vu_prof_cas,dv_prof_cas,hv_prof_cas,vv_prof_cas                &
1735     &         ,dt_prof_cas,ht_prof_cas,vt_prof_cas,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas &
1736     &         ,dth_prof_cas,hth_prof_cas,vth_prof_cas                                                 &
1737!
1738     &         ,t_mod_cas,theta_mod_cas,thv_mod_cas,thl_mod_cas                                        &
1739     &         ,qv_mod_cas,ql_mod_cas,qi_mod_cas,u_mod_cas,v_mod_cas                                   &
1740     &         ,ug_mod_cas,vg_mod_cas,w_mod_cas,omega_mod_cas                                          &
1741     &         ,du_mod_cas,hu_mod_cas,vu_mod_cas,dv_mod_cas,hv_mod_cas,vv_mod_cas                      &
1742     &         ,dt_mod_cas,ht_mod_cas,vt_mod_cas,dtrad_mod_cas,dq_mod_cas,hq_mod_cas,vq_mod_cas        &
1743     &         ,dth_mod_cas,hth_mod_cas,vth_mod_cas,mxcalc)
1744 
1745       implicit none
1746 
1747#include "YOMCST.h"
1748#include "dimensions.h"
1749
1750!-------------------------------------------------------------------------
1751! Vertical interpolation of generic case forcing data onto mod_casel levels
1752!-------------------------------------------------------------------------
1753 
1754       integer nlevmax
1755       parameter (nlevmax=41)
1756       integer nlev_cas,mxcalc
1757!       real play(llm), plev_prof(nlevmax) 
1758!       real t_prof(nlevmax),q_prof(nlevmax)
1759!       real u_prof(nlevmax),v_prof(nlevmax), w_prof(nlevmax)
1760!       real ht_prof(nlevmax),vt_prof(nlevmax)
1761!       real hq_prof(nlevmax),vq_prof(nlevmax)
1762 
1763       real play(llm), plev_prof_cas(nlev_cas) 
1764       real t_prof_cas(nlev_cas),th_prof_cas(nlev_cas),thv_prof_cas(nlev_cas),thl_prof_cas(nlev_cas)
1765       real qv_prof_cas(nlev_cas),ql_prof_cas(nlev_cas),qi_prof_cas(nlev_cas)
1766       real u_prof_cas(nlev_cas),v_prof_cas(nlev_cas)
1767       real ug_prof_cas(nlev_cas),vg_prof_cas(nlev_cas), vitw_prof_cas(nlev_cas),omega_prof_cas(nlev_cas)
1768       real du_prof_cas(nlev_cas),hu_prof_cas(nlev_cas),vu_prof_cas(nlev_cas)
1769       real dv_prof_cas(nlev_cas),hv_prof_cas(nlev_cas),vv_prof_cas(nlev_cas)
1770       real dt_prof_cas(nlev_cas),ht_prof_cas(nlev_cas),vt_prof_cas(nlev_cas),dtrad_prof_cas(nlev_cas)
1771       real dth_prof_cas(nlev_cas),hth_prof_cas(nlev_cas),vth_prof_cas(nlev_cas)
1772       real dq_prof_cas(nlev_cas),hq_prof_cas(nlev_cas),vq_prof_cas(nlev_cas)
1773 
1774       real t_mod_cas(llm),theta_mod_cas(llm),thv_mod_cas(llm),thl_mod_cas(llm)
1775       real qv_mod_cas(llm),ql_mod_cas(llm),qi_mod_cas(llm)
1776       real u_mod_cas(llm),v_mod_cas(llm)
1777       real ug_mod_cas(llm),vg_mod_cas(llm), w_mod_cas(llm),omega_mod_cas(llm)
1778       real du_mod_cas(llm),hu_mod_cas(llm),vu_mod_cas(llm)
1779       real dv_mod_cas(llm),hv_mod_cas(llm),vv_mod_cas(llm)
1780       real dt_mod_cas(llm),ht_mod_cas(llm),vt_mod_cas(llm),dtrad_mod_cas(llm)
1781       real dth_mod_cas(llm),hth_mod_cas(llm),vth_mod_cas(llm)
1782       real dq_mod_cas(llm),hq_mod_cas(llm),vq_mod_cas(llm)
1783 
1784       integer l,k,k1,k2
1785       real frac,frac1,frac2,fact
1786 
1787!       do l = 1, llm
1788!       print *,'debut interp2, play=',l,play(l)
1789!       enddo
1790!      do l = 1, nlev_cas
1791!      print *,'debut interp2, plev_prof_cas=',l,play(l),plev_prof_cas(l)
1792!      enddo
1793
1794       do l = 1, llm
1795
1796        if (play(l).ge.plev_prof_cas(nlev_cas)) then
1797 
1798        mxcalc=l
1799!        print *,'debut interp2, mxcalc=',mxcalc
1800         k1=0
1801         k2=0
1802
1803         if (play(l).le.plev_prof_cas(1)) then
1804
1805         do k = 1, nlev_cas-1
1806          if (play(l).le.plev_prof_cas(k).and. play(l).gt.plev_prof_cas(k+1)) then
1807            k1=k
1808            k2=k+1
1809          endif
1810         enddo
1811
1812         if (k1.eq.0 .or. k2.eq.0) then
1813          write(*,*) 'PB! k1, k2 = ',k1,k2
1814          write(*,*) 'l,play(l) = ',l,play(l)/100
1815         do k = 1, nlev_cas-1
1816          write(*,*) 'k,plev_prof_cas(k) = ',k,plev_prof_cas(k)/100
1817         enddo
1818         endif
1819
1820         frac = (plev_prof_cas(k2)-play(l))/(plev_prof_cas(k2)-plev_prof_cas(k1))
1821         t_mod_cas(l)= t_prof_cas(k2) - frac*(t_prof_cas(k2)-t_prof_cas(k1))
1822         theta_mod_cas(l)= th_prof_cas(k2) - frac*(th_prof_cas(k2)-th_prof_cas(k1))
1823         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
1824         thv_mod_cas(l)= thv_prof_cas(k2) - frac*(thv_prof_cas(k2)-thv_prof_cas(k1))
1825         thl_mod_cas(l)= thl_prof_cas(k2) - frac*(thl_prof_cas(k2)-thl_prof_cas(k1))
1826         qv_mod_cas(l)= qv_prof_cas(k2) - frac*(qv_prof_cas(k2)-qv_prof_cas(k1))
1827         ql_mod_cas(l)= ql_prof_cas(k2) - frac*(ql_prof_cas(k2)-ql_prof_cas(k1))
1828         qi_mod_cas(l)= qi_prof_cas(k2) - frac*(qi_prof_cas(k2)-qi_prof_cas(k1))
1829         u_mod_cas(l)= u_prof_cas(k2) - frac*(u_prof_cas(k2)-u_prof_cas(k1))
1830         v_mod_cas(l)= v_prof_cas(k2) - frac*(v_prof_cas(k2)-v_prof_cas(k1))
1831         ug_mod_cas(l)= ug_prof_cas(k2) - frac*(ug_prof_cas(k2)-ug_prof_cas(k1))
1832         vg_mod_cas(l)= vg_prof_cas(k2) - frac*(vg_prof_cas(k2)-vg_prof_cas(k1))
1833         w_mod_cas(l)= vitw_prof_cas(k2) - frac*(vitw_prof_cas(k2)-vitw_prof_cas(k1))
1834         omega_mod_cas(l)= omega_prof_cas(k2) - frac*(omega_prof_cas(k2)-omega_prof_cas(k1))
1835         du_mod_cas(l)= du_prof_cas(k2) - frac*(du_prof_cas(k2)-du_prof_cas(k1))
1836         hu_mod_cas(l)= hu_prof_cas(k2) - frac*(hu_prof_cas(k2)-hu_prof_cas(k1))
1837         vu_mod_cas(l)= vu_prof_cas(k2) - frac*(vu_prof_cas(k2)-vu_prof_cas(k1))
1838         dv_mod_cas(l)= dv_prof_cas(k2) - frac*(dv_prof_cas(k2)-dv_prof_cas(k1))
1839         hv_mod_cas(l)= hv_prof_cas(k2) - frac*(hv_prof_cas(k2)-hv_prof_cas(k1))
1840         vv_mod_cas(l)= vv_prof_cas(k2) - frac*(vv_prof_cas(k2)-vv_prof_cas(k1))
1841         dt_mod_cas(l)= dt_prof_cas(k2) - frac*(dt_prof_cas(k2)-dt_prof_cas(k1))
1842         ht_mod_cas(l)= ht_prof_cas(k2) - frac*(ht_prof_cas(k2)-ht_prof_cas(k1))
1843         vt_mod_cas(l)= vt_prof_cas(k2) - frac*(vt_prof_cas(k2)-vt_prof_cas(k1))
1844         dth_mod_cas(l)= dth_prof_cas(k2) - frac*(dth_prof_cas(k2)-dth_prof_cas(k1))
1845         hth_mod_cas(l)= hth_prof_cas(k2) - frac*(hth_prof_cas(k2)-hth_prof_cas(k1))
1846         vth_mod_cas(l)= vth_prof_cas(k2) - frac*(vth_prof_cas(k2)-vth_prof_cas(k1))
1847         dq_mod_cas(l)= dq_prof_cas(k2) - frac*(dq_prof_cas(k2)-dq_prof_cas(k1))
1848         hq_mod_cas(l)= hq_prof_cas(k2) - frac*(hq_prof_cas(k2)-hq_prof_cas(k1))
1849         vq_mod_cas(l)= vq_prof_cas(k2) - frac*(vq_prof_cas(k2)-vq_prof_cas(k1))
1850         dtrad_mod_cas(l)= dtrad_prof_cas(k2) - frac*(dtrad_prof_cas(k2)-dtrad_prof_cas(k1))
1851     
1852         else !play>plev_prof_cas(1)
1853
1854         k1=1
1855         k2=2
1856         print *,'interp2_vert, k1,k2=',plev_prof_cas(k1),plev_prof_cas(k2)
1857         frac1 = (play(l)-plev_prof_cas(k2))/(plev_prof_cas(k1)-plev_prof_cas(k2))
1858         frac2 = (play(l)-plev_prof_cas(k1))/(plev_prof_cas(k1)-plev_prof_cas(k2))
1859         t_mod_cas(l)= frac1*t_prof_cas(k1) - frac2*t_prof_cas(k2)
1860         theta_mod_cas(l)= frac1*th_prof_cas(k1) - frac2*th_prof_cas(k2)
1861         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
1862         thv_mod_cas(l)= frac1*thv_prof_cas(k1) - frac2*thv_prof_cas(k2)
1863         thl_mod_cas(l)= frac1*thl_prof_cas(k1) - frac2*thl_prof_cas(k2)
1864         qv_mod_cas(l)= frac1*qv_prof_cas(k1) - frac2*qv_prof_cas(k2)
1865         ql_mod_cas(l)= frac1*ql_prof_cas(k1) - frac2*ql_prof_cas(k2)
1866         qi_mod_cas(l)= frac1*qi_prof_cas(k1) - frac2*qi_prof_cas(k2)
1867         u_mod_cas(l)= frac1*u_prof_cas(k1) - frac2*u_prof_cas(k2)
1868         v_mod_cas(l)= frac1*v_prof_cas(k1) - frac2*v_prof_cas(k2)
1869         ug_mod_cas(l)= frac1*ug_prof_cas(k1) - frac2*ug_prof_cas(k2)
1870         vg_mod_cas(l)= frac1*vg_prof_cas(k1) - frac2*vg_prof_cas(k2)
1871         w_mod_cas(l)= frac1*vitw_prof_cas(k1) - frac2*vitw_prof_cas(k2)
1872         omega_mod_cas(l)= frac1*omega_prof_cas(k1) - frac2*omega_prof_cas(k2)
1873         du_mod_cas(l)= frac1*du_prof_cas(k1) - frac2*du_prof_cas(k2)
1874         hu_mod_cas(l)= frac1*hu_prof_cas(k1) - frac2*hu_prof_cas(k2)
1875         vu_mod_cas(l)= frac1*vu_prof_cas(k1) - frac2*vu_prof_cas(k2)
1876         dv_mod_cas(l)= frac1*dv_prof_cas(k1) - frac2*dv_prof_cas(k2)
1877         hv_mod_cas(l)= frac1*hv_prof_cas(k1) - frac2*hv_prof_cas(k2)
1878         vv_mod_cas(l)= frac1*vv_prof_cas(k1) - frac2*vv_prof_cas(k2)
1879         dt_mod_cas(l)= frac1*dt_prof_cas(k1) - frac2*dt_prof_cas(k2)
1880         ht_mod_cas(l)= frac1*ht_prof_cas(k1) - frac2*ht_prof_cas(k2)
1881         vt_mod_cas(l)= frac1*vt_prof_cas(k1) - frac2*vt_prof_cas(k2)
1882         dth_mod_cas(l)= frac1*dth_prof_cas(k1) - frac2*dth_prof_cas(k2)
1883         hth_mod_cas(l)= frac1*hth_prof_cas(k1) - frac2*hth_prof_cas(k2)
1884         vth_mod_cas(l)= frac1*vth_prof_cas(k1) - frac2*vth_prof_cas(k2)
1885         dq_mod_cas(l)= frac1*dq_prof_cas(k1) - frac2*dq_prof_cas(k2)
1886         hq_mod_cas(l)= frac1*hq_prof_cas(k1) - frac2*hq_prof_cas(k2)
1887         vq_mod_cas(l)= frac1*vq_prof_cas(k1) - frac2*vq_prof_cas(k2)
1888         dtrad_mod_cas(l)= frac1*dtrad_prof_cas(k1) - frac2*dtrad_prof_cas(k2)
1889
1890         endif ! play.le.plev_prof_cas(1)
1891
1892        else ! above max altitude of forcing file
1893 
1894!jyg
1895         fact=20.*(plev_prof_cas(nlev_cas)-play(l))/plev_prof_cas(nlev_cas) !jyg
1896         fact = max(fact,0.)                                           !jyg
1897         fact = exp(-fact)                                             !jyg
1898         t_mod_cas(l)= t_prof_cas(nlev_cas)                            !jyg
1899         theta_mod_cas(l)= th_prof_cas(nlev_cas)                       !jyg
1900         thv_mod_cas(l)= thv_prof_cas(nlev_cas)                        !jyg
1901         thl_mod_cas(l)= thl_prof_cas(nlev_cas)                        !jyg
1902         qv_mod_cas(l)= qv_prof_cas(nlev_cas)*fact                     !jyg
1903         ql_mod_cas(l)= ql_prof_cas(nlev_cas)*fact                     !jyg
1904         qi_mod_cas(l)= qi_prof_cas(nlev_cas)*fact                     !jyg
1905         u_mod_cas(l)= u_prof_cas(nlev_cas)*fact                       !jyg
1906         v_mod_cas(l)= v_prof_cas(nlev_cas)*fact                       !jyg
1907         ug_mod_cas(l)= ug_prof_cas(nlev_cas)*fact                     !jyg
1908         vg_mod_cas(l)= vg_prof_cas(nlev_cas)*fact                     !jyg
1909         w_mod_cas(l)= 0.0                                             !jyg
1910         omega_mod_cas(l)= 0.0                                         !jyg
1911         du_mod_cas(l)= du_prof_cas(nlev_cas)*fact
1912         hu_mod_cas(l)= hu_prof_cas(nlev_cas)*fact                     !jyg
1913         vu_mod_cas(l)= vu_prof_cas(nlev_cas)*fact                     !jyg
1914         dv_mod_cas(l)= dv_prof_cas(nlev_cas)*fact
1915         hv_mod_cas(l)= hv_prof_cas(nlev_cas)*fact                     !jyg
1916         vv_mod_cas(l)= vv_prof_cas(nlev_cas)*fact                     !jyg
1917         dt_mod_cas(l)= dt_prof_cas(nlev_cas) 
1918         ht_mod_cas(l)= ht_prof_cas(nlev_cas)                          !jyg
1919         vt_mod_cas(l)= vt_prof_cas(nlev_cas)                          !jyg
1920         dth_mod_cas(l)= dth_prof_cas(nlev_cas) 
1921         hth_mod_cas(l)= hth_prof_cas(nlev_cas)                        !jyg
1922         vth_mod_cas(l)= vth_prof_cas(nlev_cas)                        !jyg
1923         dq_mod_cas(l)= dq_prof_cas(nlev_cas)*fact
1924         hq_mod_cas(l)= hq_prof_cas(nlev_cas)*fact                     !jyg
1925         vq_mod_cas(l)= vq_prof_cas(nlev_cas)*fact                     !jyg
1926         dtrad_mod_cas(l)= dtrad_prof_cas(nlev_cas)*fact               !jyg
1927 
1928        endif ! play
1929 
1930       enddo ! l
1931
1932          return
1933          end
1934!***************************************************************************** 
1935
1936
1937
1938
Note: See TracBrowser for help on using the repository browser.