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

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

Significant progress for the SCM standard format

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