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

Last change on this file since 3541 was 3541, checked in by fhourdin, 5 years ago

Gros nettoyage en cours sur le 1D.
Le nouveau lmdz1d.F90 est une coquille vide qui choisit entre
old_lmdz1d.F90 (l'ancien lmdz1d.F90) et scm.F90 (le nouveau au format standard).
Plusieur fichiers sont renommés old_truc, le truc étant au format standard,
nettoyé des anciens formats.
Le 1DUTILS.h est lui même séparé entre des routines génériques venant remplacer
notamment des routines de dyn3d (la vocation d'origine de 1DUTILS.h) et
les routiles de lecture spécifiques mises dans old_1DUTILS.h
On perdra un peu de l'utilister de svn au moment de cette grosse bascule.
Mais les old_ sont faits pour ne plus bouger, et les versions standard
sont en pleine évolution.
Fredho

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