source: LMDZ6/branches/contrails/libf/phylmd/dyn1d/1DUTILS.h @ 5760

Last change on this file since 5760 was 5717, checked in by aborella, 5 weeks ago

Merge with trunk r5653

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