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

Last change on this file since 3682 was 3682, checked in by fhourdin, 4 years ago

rad_t* changed from integer to character (0/1/"adv")
Frédéric

  • Property svn:keywords set to Id
File size: 81.5 KB
Line 
1#include "conf_gcm.F90"
2
3!
4! $Id: 1DUTILS.h 3682 2020-05-26 08:03:05Z 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! FH/2020/04/08/confinement: Pour le nouveau format standard, la rugosite s'appelle z0
307       CALL getin('z0',rugos)
308
309!Config  Key  = rugosh
310!Config  Desc = coefficient de frottement
311!Config  Def  = rugos
312!Config  Help = calcul du Cdrag
313       rugosh = rugos
314       CALL getin('rugosh',rugosh)
315
316
317
318!Config  Key  = snowmass
319!Config  Desc = mass de neige de la surface en kg/m2
320!Config  Def  = 0.0000
321!Config  Help = snowmass
322       snowmass = 0.0000
323       CALL getin('snowmass',snowmass)
324
325!Config  Key  = wtsurf et wqsurf
326!Config  Desc = ???
327!Config  Def  = 0.0 0.0
328!Config  Help = 
329       wtsurf = 0.0
330       wqsurf = 0.0
331       CALL getin('wtsurf',wtsurf)
332       CALL getin('wqsurf',wqsurf)
333
334!Config  Key  = albedo
335!Config  Desc = albedo
336!Config  Def  = 0.09
337!Config  Help = 
338       albedo = 0.09
339       CALL getin('albedo',albedo)
340
341!Config  Key  = agesno
342!Config  Desc = age de la neige
343!Config  Def  = 30.0
344!Config  Help = 
345       xagesno = 30.0
346       CALL getin('agesno',xagesno)
347
348!Config  Key  = restart_runoff
349!Config  Desc = age de la neige
350!Config  Def  = 30.0
351!Config  Help = 
352       restart_runoff = 0.0
353       CALL getin('restart_runoff',restart_runoff)
354
355!Config  Key  = qsolinp
356!Config  Desc = initial bucket water content (kg/m2) when land (5std)
357!Config  Def  = 30.0
358!Config  Help = 
359       qsolinp = 1.
360       CALL getin('qsolinp',qsolinp)
361
362!Config  Key  = zpicinp
363!Config  Desc = denivellation orographie
364!Config  Def  = 0.
365!Config  Help =  input brise
366       zpicinp = 0.
367       CALL getin('zpicinp',zpicinp)
368!Config key = nudge_tsoil
369!Config  Desc = activation of soil temperature nudging
370!Config  Def  = .FALSE.
371!Config  Help = ...
372
373       nudge_tsoil=.FALSE.
374       CALL getin('nudge_tsoil',nudge_tsoil)
375
376!Config key = isoil_nudge
377!Config  Desc = level number where soil temperature is nudged
378!Config  Def  = 3
379!Config  Help = ...
380
381       isoil_nudge=3
382       CALL getin('isoil_nudge',isoil_nudge)
383
384!Config key = Tsoil_nudge
385!Config  Desc = target temperature for tsoil(isoil_nudge)
386!Config  Def  = 300.
387!Config  Help = ...
388
389       Tsoil_nudge=300.
390       CALL getin('Tsoil_nudge',Tsoil_nudge)
391
392!Config key = tau_soil_nudge
393!Config  Desc = nudging relaxation time for tsoil
394!Config  Def  = 3600.
395!Config  Help = ...
396
397       tau_soil_nudge=3600.
398       CALL getin('tau_soil_nudge',tau_soil_nudge)
399
400!----------------------------------------------------------
401! Param??tres de for??age pour les forcages communs:
402! Pour les forcages communs: ces entiers valent 0 ou 1
403! tadv= advection tempe, tadvv= adv tempe verticale, tadvh= adv tempe horizontale
404! qadv= advection q, qadvv= adv q verticale, qadvh= adv q horizontale
405! trad= 0 (rayonnement actif) ou 1 (prescrit par tend_rad) ou adv (prescir et contenu dans les tadv)
406! forcages en omega, w, vent geostrophique ou ustar
407! Parametres de nudging en u,v,t,q valent 0 ou 1 ou le temps de nudging
408!----------------------------------------------------------
409
410!Config  Key  = tadv
411!Config  Desc = forcage ou non par advection totale de T
412!Config  Def  = false
413!Config  Help = forcage ou non par advection totale de T
414       tadv =0
415       CALL getin('tadv',tadv)
416
417!Config  Key  = tadvv
418!Config  Desc = forcage ou non par advection verticale de T
419!Config  Def  = false
420!Config  Help = forcage ou non par advection verticale de T
421       tadvv =0
422       CALL getin('tadvv',tadvv)
423
424!Config  Key  = tadvh
425!Config  Desc = forcage ou non par advection horizontale de T
426!Config  Def  = false
427!Config  Help = forcage ou non par advection horizontale de T
428       tadvh =0
429       CALL getin('tadvh',tadvh)
430
431!Config  Key  = thadv
432!Config  Desc = forcage ou non par advection totale de Theta
433!Config  Def  = false
434!Config  Help = forcage ou non par advection totale de Theta
435       thadv =0
436       CALL getin('thadv',thadv)
437
438!Config  Key  = thadvv
439!Config  Desc = forcage ou non par advection verticale de Theta
440!Config  Def  = false
441!Config  Help = forcage ou non par advection verticale de Theta
442       thadvv =0
443       CALL getin('thadvv',thadvv)
444
445!Config  Key  = thadvh
446!Config  Desc = forcage ou non par advection horizontale de Theta
447!Config  Def  = false
448!Config  Help = forcage ou non par advection horizontale de Theta
449       thadvh =0
450       CALL getin('thadvh',thadvh)
451
452!Config  Key  = qadv
453!Config  Desc = forcage ou non par advection totale de Q
454!Config  Def  = false
455!Config  Help = forcage ou non par advection totale de Q
456       qadv =0
457       CALL getin('qadv',qadv)
458
459!Config  Key  = qadvv
460!Config  Desc = forcage ou non par advection verticale de Q
461!Config  Def  = false
462!Config  Help = forcage ou non par advection verticale de Q
463       qadvv =0
464       CALL getin('qadvv',qadvv)
465
466!Config  Key  = qadvh
467!Config  Desc = forcage ou non par advection horizontale de Q
468!Config  Def  = false
469!Config  Help = forcage ou non par advection horizontale de Q
470       qadvh =0
471       CALL getin('qadvh',qadvh)
472
473!Config  Key  = trad
474!Config  Desc = forcage ou non par tendance radiative
475!Config  Def  = false
476!Config  Help = forcage ou non par tendance radiative
477       trad =0
478       CALL getin('trad',trad)
479
480!Config  Key  = forc_omega
481!Config  Desc = forcage ou non par omega
482!Config  Def  = false
483!Config  Help = forcage ou non par omega
484       forc_omega =0
485       CALL getin('forc_omega',forc_omega)
486
487!Config  Key  = forc_u
488!Config  Desc = forcage ou non par u
489!Config  Def  = false
490!Config  Help = forcage ou non par u
491       forc_u =0
492       CALL getin('forc_u',forc_u)
493
494!Config  Key  = forc_v
495!Config  Desc = forcage ou non par v
496!Config  Def  = false
497!Config  Help = forcage ou non par v
498       forc_v =0
499       CALL getin('forc_v',forc_v)
500!Config  Key  = forc_w
501!Config  Desc = forcage ou non par w
502!Config  Def  = false
503!Config  Help = forcage ou non par w
504       forc_w =0
505       CALL getin('forc_w',forc_w)
506
507!Config  Key  = forc_geo
508!Config  Desc = forcage ou non par geo
509!Config  Def  = false
510!Config  Help = forcage ou non par geo
511       forc_geo =0
512       CALL getin('forc_geo',forc_geo)
513
514! Meme chose que ok_precr_ust
515!Config  Key  = forc_ustar
516!Config  Desc = forcage ou non par ustar
517!Config  Def  = false
518!Config  Help = forcage ou non par ustar
519       forc_ustar =0
520       CALL getin('forc_ustar',forc_ustar)
521       IF (forc_ustar .EQ. 1) ok_prescr_ust=.true.
522
523!Config  Key  = nudging_u
524!Config  Desc = forcage ou non par nudging sur u
525!Config  Def  = false
526!Config  Help = forcage ou non par nudging sur u
527       nudging_u =0
528       CALL getin('nudging_u',nudging_u)
529
530!Config  Key  = nudging_v
531!Config  Desc = forcage ou non par nudging sur v
532!Config  Def  = false
533!Config  Help = forcage ou non par nudging sur v
534       nudging_v =0
535       CALL getin('nudging_v',nudging_v)
536
537!Config  Key  = nudging_w
538!Config  Desc = forcage ou non par nudging sur w
539!Config  Def  = false
540!Config  Help = forcage ou non par nudging sur w
541       nudging_w =0
542       CALL getin('nudging_w',nudging_w)
543
544! RELIQUE ANCIENS FORMAT. ECRASE PAR LE SUIVANT
545!Config  Key  = nudging_q
546!Config  Desc = forcage ou non par nudging sur q
547!Config  Def  = false
548!Config  Help = forcage ou non par nudging sur q
549       nudging_qv =0
550       CALL getin('nudging_q',nudging_qv)
551       CALL getin('nudging_qv',nudging_qv)
552
553       p_nudging_u=11000.
554       p_nudging_v=11000.
555       p_nudging_t=11000.
556       p_nudging_qv=11000.
557       CALL getin('p_nudging_u',p_nudging_u)
558       CALL getin('p_nudging_v',p_nudging_v)
559       CALL getin('p_nudging_t',p_nudging_t)
560       CALL getin('p_nudging_qv',p_nudging_qv)
561
562!Config  Key  = nudging_t
563!Config  Desc = forcage ou non par nudging sur t
564!Config  Def  = false
565!Config  Help = forcage ou non par nudging sur t
566       nudging_t =0
567       CALL getin('nudging_t',nudging_t)
568
569
570
571      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
572      write(lunout,*)' Configuration des parametres du gcm1D: '
573      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
574      write(lunout,*)' restart = ', restart
575      write(lunout,*)' forcing_type = ', forcing_type
576      write(lunout,*)' time_ini = ', time_ini
577      write(lunout,*)' rlat = ', xlat
578      write(lunout,*)' rlon = ', xlon
579      write(lunout,*)' airephy = ', airefi
580      write(lunout,*)' nat_surf = ', nat_surf
581      write(lunout,*)' tsurf = ', tsurf
582      write(lunout,*)' psurf = ', psurf
583      write(lunout,*)' zsurf = ', zsurf
584      write(lunout,*)' rugos = ', rugos
585      write(lunout,*)' snowmass=', snowmass
586      write(lunout,*)' wtsurf = ', wtsurf
587      write(lunout,*)' wqsurf = ', wqsurf
588      write(lunout,*)' albedo = ', albedo
589      write(lunout,*)' xagesno = ', xagesno
590      write(lunout,*)' restart_runoff = ', restart_runoff
591      write(lunout,*)' qsolinp = ', qsolinp
592      write(lunout,*)' zpicinp = ', zpicinp
593      write(lunout,*)' nudge_tsoil = ', nudge_tsoil
594      write(lunout,*)' isoil_nudge = ', isoil_nudge
595      write(lunout,*)' Tsoil_nudge = ', Tsoil_nudge
596      write(lunout,*)' tau_soil_nudge = ', tau_soil_nudge
597      write(lunout,*)' tadv =      ', tadv
598      write(lunout,*)' tadvv =     ', tadvv
599      write(lunout,*)' tadvh =     ', tadvh
600      write(lunout,*)' thadv =     ', thadv
601      write(lunout,*)' thadvv =    ', thadvv
602      write(lunout,*)' thadvh =    ', thadvh
603      write(lunout,*)' qadv =      ', qadv
604      write(lunout,*)' qadvv =     ', qadvv
605      write(lunout,*)' qadvh =     ', qadvh
606      write(lunout,*)' trad =      ', trad
607      write(lunout,*)' forc_omega = ', forc_omega
608      write(lunout,*)' forc_w     = ', forc_w
609      write(lunout,*)' forc_geo   = ', forc_geo
610      write(lunout,*)' forc_ustar = ', forc_ustar
611      write(lunout,*)' nudging_u  = ', nudging_u
612      write(lunout,*)' nudging_v  = ', nudging_v
613      write(lunout,*)' nudging_t  = ', nudging_t
614      write(lunout,*)' nudging_qv  = ', nudging_qv
615      IF (forcing_type .eq.40) THEN
616        write(lunout,*) '--- Forcing type GCSS Old --- with:'
617        write(lunout,*)'imp_fcg',imp_fcg_gcssold
618        write(lunout,*)'ts_fcg',ts_fcg_gcssold
619        write(lunout,*)'tp_fcg',Tp_fcg_gcssold
620        write(lunout,*)'tp_ini',Tp_ini_gcssold
621        write(lunout,*)'xturb_fcg',xTurb_fcg_gcssold
622      ENDIF
623
624      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
625      write(lunout,*)
626!
627      RETURN
628      END
629!     
630      SUBROUTINE conf_unicol_std
631!
632#ifdef CPP_IOIPSL
633      use IOIPSL
634#else
635! if not using IOIPSL, we still need to use (a local version of) getin
636      use ioipsl_getincom
637#endif
638      USE print_control_mod, ONLY: lunout
639      IMPLICIT NONE
640!-----------------------------------------------------------------------
641!     Auteurs :   A. Lahellec  - adaptation au format standard.
642!
643!   Declarations :
644!   --------------
645
646#include "compar1d_std.h"
647#include "flux_arp.h"
648#include "tsoilnudge.h"
649#include "fcg_gcssold.h"
650#include "fcg_racmo.h"
651!
652!
653!   local:
654!   ------
655
656!      CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
657     
658!
659!  -------------------------------------------------------------------
660!
661!      .........    Initilisation parametres du lmdz1D      ..........
662!
663!---------------------------------------------------------------------
664!   initialisations:
665!   ----------------
666
667!Config  Key  = lunout
668!Config  Desc = unite de fichier pour les impressions
669!Config  Def  = 6
670!Config  Help = unite de fichier pour les impressions
671!Config         (defaut sortie standard = 6)
672      lunout=6
673!      CALL getin('lunout', lunout)
674      IF (lunout /= 5 .and. lunout /= 6) THEN
675        OPEN(lunout,FILE='lmdz.out')
676      ENDIF
677
678!Config  Key  = prt_level
679!Config  Desc = niveau d'impressions de debogage
680!Config  Def  = 0
681!Config  Help = Niveau d'impression pour le debogage
682!Config         (0 = minimum d'impression)
683!      prt_level = 0
684!      CALL getin('prt_level',prt_level)
685
686!-----------------------------------------------------------------------
687!  Parametres de controle du run:
688!-----------------------------------------------------------------------
689
690!Config  Key  = restart
691!Config  Desc = on repart des startphy et start1dyn
692!Config  Def  = false
693!Config  Help = les fichiers restart doivent etre renomme en start
694       restart =.false.
695       CALL getin('restart',restart)
696
697!----------------------------------------------------------
698! Parametres de forcage pour les forcages communs:
699! Voir ici: https://github.com/romainroehrig/DEPHY-SCM/blob/master/DEPHY_Format_Version_0.pdf
700! Pour les forcages communs: ces entiers valent 0 ou 1
701! adv_temp= advection tempe, theta ou thetal, qv,qt,rv ou rt
702! rad_temp= 0 (rayonnement actif) ou 1 (prescrit par tend_rad) ou adv (prescir et contenu dans les adv_temp)
703! idem rad_theta et rad_thetal 
704! forcages en omega, w, vent geostrophique ou ustar
705! Parametres de nudging en u,v,temp, theta, thetal,qv, qt, rv, rt valent 0 ou 1 ou le temps de nudging
706! p_nudging_xxx pression (Pa) a partir de laquelle appliquer le nudging de xxx
707! ou z_nudging_xxx hauteur(m) a partir de laquelle appliquer le nudging de xxx
708!----------------------------------------------------------
709!
710!Parametres de forcage
711!Config  Key  = adv_temp
712!Config  Desc = forcage ou non par advection de T
713!Config  Def  = false
714!Config  Help = forcage ou non par advection de T
715       adv_temp =0
716       CALL getin('adv_temp',adv_temp)
717
718!
719!Parametres de forcage
720!Config  Key  = adv_theta
721!Config  Desc = forcage ou non par advection de Theta
722!Config  Def  = false
723!Config  Help = forcage ou non par advection de Theta
724       adv_theta =0
725       CALL getin('adv_theta',adv_theta)
726
727!
728!Parametres de forcage
729!Config  Key  = adv_thetal
730!Config  Desc = forcage ou non par advection de Thetal
731!Config  Def  = false
732!Config  Help = forcage ou non par advection de Thetal
733       adv_thetal =0
734       CALL getin('adv_thetal',adv_thetal)
735
736!
737!Parametres de forcage
738!Config  Key  = rad_temp
739!Config  Desc = forcage par tendance radiative en tempe
740!Config  Def  = false
741!Config  Help = forcage par tendance radiative en tempe
742       rad_temp ="0"
743       CALL getin('rad_temp',rad_temp)
744
745!
746!Parametres de forcage
747!Config  Key  = rad_theta
748!Config  Desc = forcage par tendance radiative en theta
749!Config  Def  = false
750!Config  Help = forcage par tendance radiative en theta
751       rad_theta ="0"
752       CALL getin('rad_theta',rad_theta)
753
754!
755!Parametres de forcage
756!Config  Key  = rad_thetal
757!Config  Desc = forcage par tendance radiative en thetal
758!Config  Def  = false
759!Config  Help = forcage par tendance radiative en thetal
760       rad_thetal ="0"
761       CALL getin('rad_thetal',rad_thetal)
762
763!
764!Parametres de forcage
765!Config  Key  = adv_qv
766!Config  Desc = forcage ou non par advection de qv
767!Config  Def  = false
768!Config  Help = forcage ou non par advection de qv
769       adv_qv =0
770       CALL getin('adv_qv',adv_qv)
771
772!
773!Parametres de forcage
774!Config  Key  = adv_qt
775!Config  Desc = forcage ou non par advection de qt
776!Config  Def  = false
777!Config  Help = forcage ou non par advection de qt
778       adv_qt =0
779       CALL getin('adv_qt',adv_qt)
780
781!
782!Parametres de forcage
783!Config  Key  = adv_rv
784!Config  Desc = forcage ou non par advection de rv
785!Config  Def  = false
786!Config  Help = forcage ou non par advection de rv
787       adv_rv =0
788       CALL getin('adv_rv',adv_rv)
789
790!
791!Parametres de forcage
792!Config  Key  = adv_rt
793!Config  Desc = forcage ou non par advection de rt
794!Config  Def  = false
795!Config  Help = forcage ou non par advection de rt
796       adv_rt =0
797       CALL getin('adv_rt',adv_rt)
798
799!
800!Parametres de forcage
801!Config  Key  = nudging_temp
802!Config  Desc = forcage ou non par advection de tempe
803!Config  Def  = false
804!Config  Help = forcage ou non par advection de tempe
805       nudging_temp =0
806       CALL getin('nudging_temp',nudging_temp)
807
808!
809!Parametres de forcage
810!Config  Key  = nudging_theta
811!Config  Desc = forcage ou non par advection de theta
812!Config  Def  = false
813!Config  Help = forcage ou non par advection de theta
814       nudging_theta =0
815       CALL getin('nudging_theta',nudging_theta)
816
817!
818!Parametres de forcage
819!Config  Key  = nudging_thetal
820!Config  Desc = forcage ou non par advection de thetal
821!Config  Def  = false
822!Config  Help = forcage ou non par advection de thetal
823       nudging_thetal =0
824       CALL getin('nudging_thetal',nudging_thetal)
825
826!
827!Parametres de forcage
828!Config  Key  = nudging_qv
829!Config  Desc = forcage ou non par advection de qv
830!Config  Def  = false
831!Config  Help = forcage ou non par advection de qv
832       nudging_qv =0
833       CALL getin('nudging_qv',nudging_qv)
834
835!
836!Parametres de forcage
837!Config  Key  = nudging_qt
838!Config  Desc = forcage ou non par advection de qt
839!Config  Def  = false
840!Config  Help = forcage ou non par advection de qt
841       nudging_qt =0
842       CALL getin('nudging_qt',nudging_qt)
843
844!
845!Parametres de forcage
846!Config  Key  = nudging_rv
847!Config  Desc = forcage ou non par advection de rv
848!Config  Def  = false
849!Config  Help = forcage ou non par advection de rv
850       nudging_rv =0
851       CALL getin('nudging_rv',nudging_rv)
852
853!
854!Parametres de forcage
855!Config  Key  = nudging_rt
856!Config  Desc = forcage ou non par advection de rt
857!Config  Def  = false
858!Config  Help = forcage ou non par advection de rt
859       nudging_rt =0
860       CALL getin('nudging_rt',nudging_rt)
861
862!
863!Parametres de forcage
864!Config  Key  = nudging_u
865!Config  Desc = forcage ou non par advection de u wind
866!Config  Def  = false
867!Config  Help = forcage ou non par advection de u wind
868       nudging_u =0
869       CALL getin('nudging_u',nudging_u)
870
871!
872!Parametres de forcage
873!Config  Key  = nudging_v
874!Config  Desc = forcage ou non par advection de v wind
875!Config  Def  = false
876!Config  Help = forcage ou non par advection de v wind
877       nudging_v =0
878       CALL getin('nudging_v',nudging_v)
879
880!
881!Parametres de forcage
882!Config  Key  = p_nudging_temp
883!Config  Desc = Pressure (Pa) above which tempe should be nudged
884!Config  Def  = false
885!Config  Help = Pressure (Pa) above which tempe should be nudged
886       p_nudging_temp =11000.
887       CALL getin('p_nudging_tempe',p_nudging_temp)
888
889!
890!Parametres de forcage
891!Config  Key  = p_nudging_theta
892!Config  Desc = Pressure (Pa) above which theta should be nudged
893!Config  Def  = false
894!Config  Help = Pressure (Pa) above which theta should be nudged
895       p_nudging_theta =11000.
896       CALL getin('p_nudging_theta',p_nudging_theta)
897
898!
899!Parametres de forcage
900!Config  Key  = p_nudging_thetal
901!Config  Desc = Pressure (Pa) above which thetal should be nudged
902!Config  Def  = false
903!Config  Help = Pressure (Pa) above which thetal should be nudged
904       p_nudging_thetal =11000.
905       CALL getin('p_nudging_thetal',p_nudging_thetal)
906
907!
908!Parametres de forcage
909!Config  Key  = p_nudging_qv
910!Config  Desc = Pressure (Pa) above which qv should be nudged
911!Config  Def  = false
912!Config  Help = Pressure (Pa) above which qv should be nudged
913       p_nudging_qv =11000.
914       CALL getin('p_nudging_qv',p_nudging_qv)
915
916!
917!Parametres de forcage
918!Config  Key  = p_nudging_qt
919!Config  Desc = Pressure (Pa) above which qt should be nudged
920!Config  Def  = false
921!Config  Help = Pressure (Pa) above which qt should be nudged
922       p_nudging_qt =11000.
923       CALL getin('p_nudging_qt',p_nudging_qt)
924
925!
926!Parametres de forcage
927!Config  Key  = p_nudging_rv
928!Config  Desc = Pressure (Pa) above which rv should be nudged
929!Config  Def  = false
930!Config  Help = Pressure (Pa) above which rv should be nudged
931       p_nudging_rv =11000.
932       CALL getin('p_nudging_rv',p_nudging_rv)
933
934!
935!Parametres de forcage
936!Config  Key  = p_nudging_rt
937!Config  Desc = Pressure (Pa) above which rt should be nudged
938!Config  Def  = false
939!Config  Help = Pressure (Pa) above which rt should be nudged
940       p_nudging_rt =11000.
941       CALL getin('p_nudging_rt',p_nudging_rt)
942
943!
944!Parametres de forcage
945!Config  Key  = p_nudging_u
946!Config  Desc = Pressure (Pa) above which u should be nudged
947!Config  Def  = false
948!Config  Help = Pressure (Pa) above which u should be nudged
949       p_nudging_u =11000.
950       CALL getin('p_nudging_u',p_nudging_u)
951
952!
953!Parametres de forcage
954!Config  Key  = p_nudging_v
955!Config  Desc = Pressure (Pa) above which v should be nudged
956!Config  Def  = false
957!Config  Help = Pressure (Pa) above which v should be nudged
958       p_nudging_v =11000.
959       CALL getin('p_nudging_v',p_nudging_v)
960
961!
962!Parametres de forcage
963!Config  Key  = z_nudging_temp
964!Config  Desc = Height (m) above which tempe should be nudged
965!Config  Def  = false
966!Config  Help = Height (m) above which tempe should be nudged
967       z_nudging_temp=0.
968       CALL getin('z_nudging_tempe',z_nudging_temp)
969
970!
971!Parametres de forcage
972!Config  Key  = z_nudging_theta
973!Config  Desc = Height (m) above which theta should be nudged
974!Config  Def  = false
975!Config  Help = Height (m) above which theta should be nudged
976       z_nudging_theta=0.
977       CALL getin('z_nudging_theta',z_nudging_theta)
978
979!
980!Parametres de forcage
981!Config  Key  = z_nudging_thetal
982!Config  Desc = Height (m) above which thetal should be nudged
983!Config  Def  = false
984!Config  Help = Height (m) above which thetal should be nudged
985       z_nudging_thetal=0.
986       CALL getin('z_nudging_thetal',z_nudging_thetal)
987
988!
989!Parametres de forcage
990!Config  Key  = z_nudging_qv
991!Config  Desc = Height (m) above which qv should be nudged
992!Config  Def  = false
993!Config  Help = Height (m) above which qv should be nudged
994       z_nudging_qv=0.
995       CALL getin('z_nudging_qv',z_nudging_qv)
996
997!
998!Parametres de forcage
999!Config  Key  = z_nudging_qt
1000!Config  Desc = Height (m) above which qt should be nudged
1001!Config  Def  = false
1002!Config  Help = Height (m) above which qt should be nudged
1003       z_nudging_qt=0.
1004       CALL getin('z_nudging_qt',z_nudging_qt)
1005
1006!
1007!Parametres de forcage
1008!Config  Key  = z_nudging_rv
1009!Config  Desc = Height (m) above which rv should be nudged
1010!Config  Def  = false
1011!Config  Help = Height (m) above which rv should be nudged
1012       z_nudging_rv=0.
1013       CALL getin('z_nudging_rv',z_nudging_rv)
1014
1015!
1016!Parametres de forcage
1017!Config  Key  = z_nudging_rt
1018!Config  Desc = Height (m) above which rt should be nudged
1019!Config  Def  = false
1020!Config  Help = Height (m) above which rt should be nudged
1021       z_nudging_rt=0.
1022       CALL getin('z_nudging_rt',z_nudging_rt)
1023
1024!
1025!Parametres de forcage
1026!Config  Key  = z_nudging_u
1027!Config  Desc = Height (m) above which u should be nudged
1028!Config  Def  = false
1029!Config  Help = Height (m) above which u should be nudged
1030       z_nudging_u=0.
1031       CALL getin('z_nudging_u',z_nudging_u)
1032
1033!
1034!Parametres de forcage
1035!Config  Key  = z_nudging_v
1036!config  desc = height (m) above which v should be nudged
1037!config  def  = false
1038!config  help = height (m) above which v should be nudged
1039       z_nudging_v=0.
1040       call getin('z_nudging_v',z_nudging_v)
1041
1042!config  key  = ok_flux_surf
1043!config  desc = forcage ou non par les flux de surface
1044!config  def  = false
1045!config  help = forcage ou non par les flux de surface
1046       ok_flux_surf =.false.
1047       call getin('ok_flux_surf',ok_flux_surf)
1048
1049!config  key  = ok_prescr_ust
1050!config  desc = ustar impose ou non
1051!config  def  = false
1052!config  help = ustar impose ou non
1053       ok_prescr_ust = .false.
1054       call getin('ok_prescr_ust',ok_prescr_ust)
1055
1056!config  key  = ok_old_disvert
1057!config  desc = utilisation de l ancien programme disvert0 (dans 1dutils.h)
1058!config  def  = false
1059!config  help = utilisation de l ancien programme disvert0 (dans 1dutils.h)
1060       ok_old_disvert = .false.
1061       call getin('ok_old_disvert',ok_old_disvert)
1062
1063!config  key  = time_ini
1064!config  desc = meaningless in this  case
1065!config  def  = 0.
1066!config  help = 
1067       tsurf = 0.
1068       call getin('time_ini',time_ini)
1069
1070!config  key  = rlat et rlon
1071!config  desc = latitude et longitude
1072!config  def  = 0.0  0.0
1073!config  help = fixe la position de la colonne
1074       xlat = 0.
1075       xlon = 0.
1076       call getin('rlat',xlat)
1077       call getin('rlon',xlon)
1078
1079!config  key  = airephy
1080!config  desc = grid cell area
1081!config  def  = 1.e11
1082!config  help = 
1083       airefi = 1.e11
1084       call getin('airephy',airefi)
1085
1086!config  key  = nat_surf
1087!config  desc = surface type
1088!config  def  = 0 (ocean)
1089!config  help = 0=ocean,1=land,2=glacier,3=banquise
1090       nat_surf = 0.
1091       call getin('nat_surf',nat_surf)
1092
1093!config  key  = tsurf
1094!config  desc = surface temperature
1095!config  def  = 290.
1096!config  help = not used if type_ts_forcing=1 in lmdz1d.f
1097       tsurf = 290.
1098       call getin('tsurf',tsurf)
1099
1100!config  key  = psurf
1101!config  desc = surface pressure
1102!config  def  = 102400.
1103!config  help = 
1104       psurf = 102400.
1105       call getin('psurf',psurf)
1106
1107!config  key  = zsurf
1108!config  desc = surface altitude
1109!config  def  = 0.
1110!config  help = 
1111       zsurf = 0.
1112       call getin('zsurf',zsurf)
1113
1114!config  key  = rugos
1115!config  desc = coefficient de frottement
1116!config  def  = 0.0001
1117!config  help = calcul du cdrag
1118       rugos = 0.0001
1119       call getin('rugos',rugos)
1120! fh/2020/04/08/confinement: pour le nouveau format standard, la rugosite s'appelle z0
1121       call getin('z0',rugos)
1122
1123!config  key  = rugosh
1124!config  desc = coefficient de frottement
1125!config  def  = rugos
1126!config  help = calcul du cdrag
1127       rugosh = rugos
1128       call getin('rugosh',rugosh)
1129
1130!config  key  = snowmass
1131!config  desc = mass de neige de la surface en kg/m2
1132!config  def  = 0.0000
1133!config  help = snowmass
1134       snowmass = 0.0000
1135       call getin('snowmass',snowmass)
1136
1137!config  key  = wtsurf et wqsurf
1138!config  desc = ???
1139!config  def  = 0.0 0.0
1140!config  help = 
1141       wtsurf = 0.0
1142       wqsurf = 0.0
1143       call getin('wtsurf',wtsurf)
1144       call getin('wqsurf',wqsurf)
1145
1146!config  key  = albedo
1147!config  desc = albedo
1148!config  def  = 0.09
1149!config  help = 
1150       albedo = 0.09
1151       call getin('albedo',albedo)
1152
1153!config  key  = agesno
1154!config  desc = age de la neige
1155!config  def  = 30.0
1156!config  help = 
1157       xagesno = 30.0
1158       call getin('agesno',xagesno)
1159
1160!config  key  = restart_runoff
1161!config  desc = age de la neige
1162!config  def  = 30.0
1163!config  help = 
1164       restart_runoff = 0.0
1165       call getin('restart_runoff',restart_runoff)
1166
1167!config  key  = qsolinp
1168!config  desc = initial bucket water content (kg/m2) when land (5std)
1169!config  def  = 30.0
1170!config  help = 
1171       qsolinp = 1.
1172       call getin('qsolinp',qsolinp)
1173
1174!config  key  = zpicinp
1175!config  desc = denivellation orographie
1176!config  def  = 0.
1177!config  help =  input brise
1178       zpicinp = 0.
1179       call getin('zpicinp',zpicinp)
1180
1181!config key = nudge_tsoil
1182!config  desc = activation of soil temperature nudging
1183!config  def  = .false.
1184!config  help = ...
1185       nudge_tsoil=.false.
1186       call getin('nudge_tsoil',nudge_tsoil)
1187
1188!config key = isoil_nudge
1189!config  desc = level number where soil temperature is nudged
1190!config  def  = 3
1191!config  help = ...
1192       isoil_nudge=3
1193       call getin('isoil_nudge',isoil_nudge)
1194
1195!config key = tsoil_nudge
1196!config  desc = target temperature for tsoil(isoil_nudge)
1197!config  def  = 300.
1198!config  help = ...
1199       tsoil_nudge=300.
1200       call getin('tsoil_nudge',tsoil_nudge)
1201
1202!config key = tau_soil_nudge
1203!config  desc = nudging relaxation time for tsoil
1204!config  def  = 3600.
1205!config  help = ...
1206       tau_soil_nudge=3600.
1207       call getin('tau_soil_nudge',tau_soil_nudge)
1208
1209!config  key  = forc_omega
1210!config  desc = forcage ou non par omega
1211!config  def  = false
1212!config  help = forcage ou non par omega
1213       forc_omega =0
1214       call getin('forc_omega',forc_omega)
1215
1216!config  key  = forc_w
1217!config  desc = forcage ou non par w
1218!config  def  = false
1219!config  help = forcage ou non par w
1220       forc_w =0
1221       call getin('forc_w',forc_w)
1222
1223!config  key  = forc_geo
1224!config  desc = forcage ou non par geo
1225!config  def  = false
1226!config  help = forcage ou non par geo
1227       forc_geo =0
1228       call getin('forc_geo',forc_geo)
1229
1230! meme chose que ok_precr_ust
1231!config  key  = forc_ustar
1232!config  desc = forcage ou non par ustar
1233!config  def  = false
1234!config  help = forcage ou non par ustar
1235       forc_ustar =0
1236       call getin('forc_ustar',forc_ustar)
1237       if (forc_ustar .eq. 1) ok_prescr_ust=.true.
1238
1239
1240      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
1241      write(lunout,*)' configuration des parametres du gcm1d: '
1242      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
1243      write(lunout,*)' restart = ', restart
1244      write(lunout,*)' forcing_type = ', forcing_type
1245      write(lunout,*)' time_ini = ', time_ini
1246      write(lunout,*)' rlat = ', xlat
1247      write(lunout,*)' rlon = ', xlon
1248      write(lunout,*)' airephy = ', airefi
1249      write(lunout,*)' nat_surf = ', nat_surf
1250      write(lunout,*)' tsurf = ', tsurf
1251      write(lunout,*)' psurf = ', psurf
1252      write(lunout,*)' zsurf = ', zsurf
1253      write(lunout,*)' rugos = ', rugos
1254      write(lunout,*)' snowmass=', snowmass
1255      write(lunout,*)' wtsurf = ', wtsurf
1256      write(lunout,*)' wqsurf = ', wqsurf
1257      write(lunout,*)' albedo = ', albedo
1258      write(lunout,*)' xagesno = ', xagesno
1259      write(lunout,*)' restart_runoff = ', restart_runoff
1260      write(lunout,*)' qsolinp = ', qsolinp
1261      write(lunout,*)' zpicinp = ', zpicinp
1262      write(lunout,*)' nudge_tsoil = ', nudge_tsoil
1263      write(lunout,*)' isoil_nudge = ', isoil_nudge
1264      write(lunout,*)' tsoil_nudge = ', tsoil_nudge
1265      write(lunout,*)' tau_soil_nudge = ', tau_soil_nudge
1266      write(lunout,*)' adv_temp =      ', adv_temp
1267      write(lunout,*)' adv_theta =      ', adv_theta
1268      write(lunout,*)' adv_thetal =      ', adv_thetal
1269      write(lunout,*)' rad_temp =      ', rad_temp
1270      write(lunout,*)' rad_theta =      ', rad_theta
1271      write(lunout,*)' rad_thetal =      ', rad_thetal
1272      write(lunout,*)' adv_qv =      ', adv_qv
1273      write(lunout,*)' adv_qt =      ', adv_qt
1274      write(lunout,*)' adv_rv =      ', adv_rv
1275      write(lunout,*)' adv_rt =      ', adv_rt
1276      write(lunout,*)' nudging_temp =      ', nudging_temp
1277      write(lunout,*)' nudging_theta =      ', nudging_theta
1278      write(lunout,*)' nudging_thetal =      ', nudging_thetal
1279      write(lunout,*)' nudging_qv =      ', nudging_qv
1280      write(lunout,*)' nudging_qt =      ', nudging_qt
1281      write(lunout,*)' nudging_rv =      ', nudging_rv
1282      write(lunout,*)' nudging_rt =      ', nudging_rt
1283      write(lunout,*)' p_nudging_temp =      ', p_nudging_temp
1284      write(lunout,*)' p_nudging_theta =      ', p_nudging_theta
1285      write(lunout,*)' p_nudging_thetal =      ', p_nudging_thetal
1286      write(lunout,*)' p_nudging_qv =      ', p_nudging_qv
1287      write(lunout,*)' p_nudging_qt =      ', p_nudging_qt
1288      write(lunout,*)' p_nudging_rv =      ', p_nudging_rv
1289      write(lunout,*)' p_nudging_rt =      ', p_nudging_rt
1290      write(lunout,*)' z_nudging_temp =      ', z_nudging_temp
1291      write(lunout,*)' z_nudging_theta =      ', z_nudging_theta
1292      write(lunout,*)' z_nudging_thetal =      ', z_nudging_thetal
1293      write(lunout,*)' z_nudging_qv =      ', z_nudging_qv
1294      write(lunout,*)' z_nudging_qt =      ', z_nudging_qt
1295      write(lunout,*)' z_nudging_rv =      ', z_nudging_rv
1296      write(lunout,*)' z_nudging_rt =      ', z_nudging_rt
1297      write(lunout,*)' forc_omega = ', forc_omega
1298      write(lunout,*)' forc_w     = ', forc_w
1299      write(lunout,*)' forc_geo   = ', forc_geo
1300      write(lunout,*)' forc_ustar = ', forc_ustar
1301      IF (forcing_type .eq.40) THEN
1302        write(lunout,*) '--- Forcing type GCSS Old --- with:'
1303        write(lunout,*)'imp_fcg',imp_fcg_gcssold
1304        write(lunout,*)'ts_fcg',ts_fcg_gcssold
1305        write(lunout,*)'tp_fcg',Tp_fcg_gcssold
1306        write(lunout,*)'tp_ini',Tp_ini_gcssold
1307        write(lunout,*)'xturb_fcg',xTurb_fcg_gcssold
1308      ENDIF
1309
1310      write(lunout,*)' +++++++++++++++++++++++++++++++++++++++'
1311      write(lunout,*)
1312!
1313      RETURN
1314      END
1315!
1316! $Id: dyn1deta0.F 1279 2010/07/30 A Lahellec$
1317!
1318!
1319      SUBROUTINE dyn1deta0(fichnom,plev,play,phi,phis,presnivs,                 &
1320     &                          ucov,vcov,temp,q,omega2)
1321      USE dimphy
1322      USE mod_grid_phy_lmdz
1323      USE mod_phys_lmdz_para
1324      USE iophy
1325      USE phys_state_var_mod
1326      USE iostart
1327      USE write_field_phy
1328      USE infotrac
1329      use control_mod
1330      USE comconst_mod, ONLY: im, jm, lllm
1331      USE logic_mod, ONLY: fxyhypb, ysinus
1332      USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn
1333
1334      IMPLICIT NONE
1335!=======================================================
1336! Ecriture du fichier de redemarrage sous format NetCDF
1337!=======================================================
1338!   Declarations:
1339!   -------------
1340      include "dimensions.h"
1341!!#include "control.h"
1342      include "netcdf.inc"
1343
1344!   Arguments:
1345!   ----------
1346      CHARACTER*(*) fichnom
1347!Al1 plev tronque pour .nc mais plev(klev+1):=0
1348      real :: plev(klon,klev+1),play (klon,klev),phi(klon,klev)
1349      real :: presnivs(klon,klev)
1350      real :: ucov(klon,klev),vcov(klon,klev),temp(klon,klev)
1351      real :: q(klon,klev,nqtot),omega2(klon,klev)
1352!      real :: ug(klev),vg(klev),fcoriolis
1353      real :: phis(klon) 
1354
1355!   Variables locales pour NetCDF:
1356!   ------------------------------
1357      INTEGER iq
1358      INTEGER length
1359      PARAMETER (length = 100)
1360      REAL tab_cntrl(length) ! tableau des parametres du run
1361      character*4 nmq(nqtot)
1362      character*12 modname
1363      character*80 abort_message
1364      LOGICAL found
1365
1366      modname = 'dyn1deta0 : '
1367!!      nmq(1)="vap"
1368!!      nmq(2)="cond"
1369!!      do iq=3,nqtot
1370!!        write(nmq(iq),'("tra",i1)') iq-2
1371!!      enddo
1372      DO iq = 1,nqtot
1373        nmq(iq) = trim(tname(iq))
1374      ENDDO
1375      print*,'in dyn1deta0 ',fichnom,klon,klev,nqtot
1376      CALL open_startphy(fichnom)
1377      print*,'after open startphy ',fichnom,nmq
1378
1379!
1380! Lecture des parametres de controle:
1381!
1382      CALL get_var("controle",tab_cntrl)
1383       
1384
1385      im         = tab_cntrl(1)
1386      jm         = tab_cntrl(2)
1387      lllm       = tab_cntrl(3)
1388      day_ref    = tab_cntrl(4)
1389      annee_ref  = tab_cntrl(5)
1390!      rad        = tab_cntrl(6)
1391!      omeg       = tab_cntrl(7)
1392!      g          = tab_cntrl(8)
1393!      cpp        = tab_cntrl(9)
1394!      kappa      = tab_cntrl(10)
1395!      daysec     = tab_cntrl(11)
1396!      dtvr       = tab_cntrl(12)
1397!      etot0      = tab_cntrl(13)
1398!      ptot0      = tab_cntrl(14)
1399!      ztot0      = tab_cntrl(15)
1400!      stot0      = tab_cntrl(16)
1401!      ang0       = tab_cntrl(17)
1402!      pa         = tab_cntrl(18)
1403!      preff      = tab_cntrl(19)
1404!
1405!      clon       = tab_cntrl(20)
1406!      clat       = tab_cntrl(21)
1407!      grossismx  = tab_cntrl(22)
1408!      grossismy  = tab_cntrl(23)
1409!
1410      IF ( tab_cntrl(24).EQ.1. )  THEN
1411        fxyhypb  =.true.
1412!        dzoomx   = tab_cntrl(25)
1413!        dzoomy   = tab_cntrl(26)
1414!        taux     = tab_cntrl(28)
1415!        tauy     = tab_cntrl(29)
1416      ELSE
1417        fxyhypb = .false.
1418        ysinus  = .false.
1419        IF( tab_cntrl(27).EQ.1. ) ysinus =.true. 
1420      ENDIF
1421
1422      day_ini = tab_cntrl(30)
1423      itau_dyn = tab_cntrl(31)
1424!   .................................................................
1425!
1426!
1427!      PRINT*,'rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa
1428!Al1
1429       Print*,'day_ref,annee_ref,day_ini,itau_dyn',                         &
1430     &              day_ref,annee_ref,day_ini,itau_dyn
1431
1432!  Lecture des champs
1433!
1434      CALL get_field("play",play,found)
1435      IF (.NOT. found) PRINT*, modname//'Le champ <Play> est absent'
1436      CALL get_field("phi",phi,found)
1437      IF (.NOT. found) PRINT*, modname//'Le champ <Phi> est absent'
1438      CALL get_field("phis",phis,found)
1439      IF (.NOT. found) PRINT*, modname//'Le champ <Phis> est absent'
1440      CALL get_field("presnivs",presnivs,found)
1441      IF (.NOT. found) PRINT*, modname//'Le champ <Presnivs> est absent'
1442      CALL get_field("ucov",ucov,found)
1443      IF (.NOT. found) PRINT*, modname//'Le champ <ucov> est absent'
1444      CALL get_field("vcov",vcov,found)
1445      IF (.NOT. found) PRINT*, modname//'Le champ <vcov> est absent'
1446      CALL get_field("temp",temp,found)
1447      IF (.NOT. found) PRINT*, modname//'Le champ <temp> est absent'
1448      CALL get_field("omega2",omega2,found)
1449      IF (.NOT. found) PRINT*, modname//'Le champ <omega2> est absent'
1450      plev(1,klev+1)=0.
1451      CALL get_field("plev",plev(:,1:klev),found)
1452      IF (.NOT. found) PRINT*, modname//'Le champ <Plev> est absent'
1453
1454      Do iq=1,nqtot
1455        CALL get_field("q"//nmq(iq),q(:,:,iq),found)
1456        IF (.NOT.found)PRINT*, modname//'Le champ <q'//nmq//'> est absent'
1457      EndDo
1458
1459      CALL close_startphy
1460      print*,' close startphy',fichnom,play(1,1),play(1,klev),temp(1,klev)
1461!
1462      RETURN
1463      END
1464!
1465! $Id: dyn1dredem.F 1279 2010/07/29 A Lahellec$
1466!
1467!
1468      SUBROUTINE dyn1dredem(fichnom,plev,play,phi,phis,presnivs,           &
1469     &                          ucov,vcov,temp,q,omega2)
1470      USE dimphy
1471      USE mod_grid_phy_lmdz
1472      USE mod_phys_lmdz_para
1473      USE phys_state_var_mod
1474      USE iostart
1475      USE infotrac
1476      use control_mod
1477      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
1478      USE logic_mod, ONLY: fxyhypb, ysinus
1479      USE temps_mod, ONLY: annee_ref,day_end,day_ref,itau_dyn,itaufin
1480
1481      IMPLICIT NONE
1482!=======================================================
1483! Ecriture du fichier de redemarrage sous format NetCDF
1484!=======================================================
1485!   Declarations:
1486!   -------------
1487      include "dimensions.h"
1488!!#include "control.h"
1489      include "netcdf.inc"
1490
1491!   Arguments:
1492!   ----------
1493      CHARACTER*(*) fichnom
1494!Al1 plev tronque pour .nc mais plev(klev+1):=0
1495      real :: plev(klon,klev),play (klon,klev),phi(klon,klev)
1496      real :: presnivs(klon,klev)
1497      real :: ucov(klon,klev),vcov(klon,klev),temp(klon,klev)
1498      real :: q(klon,klev,nqtot)
1499      real :: omega2(klon,klev),rho(klon,klev+1)
1500!      real :: ug(klev),vg(klev),fcoriolis
1501      real :: phis(klon) 
1502
1503!   Variables locales pour NetCDF:
1504!   ------------------------------
1505      INTEGER nid
1506      INTEGER ierr
1507      INTEGER iq,l
1508      INTEGER length
1509      PARAMETER (length = 100)
1510      REAL tab_cntrl(length) ! tableau des parametres du run
1511      character*4 nmq(nqtot)
1512      character*20 modname
1513      character*80 abort_message
1514!
1515      INTEGER pass
1516
1517      CALL open_restartphy(fichnom)
1518      print*,'redm1 ',fichnom,klon,klev,nqtot
1519!!      nmq(1)="vap"
1520!!      nmq(2)="cond"
1521!!      nmq(3)="tra1"
1522!!      nmq(4)="tra2"
1523      DO iq = 1,nqtot
1524        nmq(iq) = trim(tname(iq))
1525      ENDDO
1526
1527!     modname = 'dyn1dredem'
1528!     ierr = NF_OPEN(fichnom, NF_WRITE, nid)
1529!     IF (ierr .NE. NF_NOERR) THEN
1530!        abort_message="Pb. d ouverture "//fichnom
1531!        CALL abort_gcm('Modele 1D',abort_message,1)
1532!     ENDIF
1533
1534      DO l=1,length
1535       tab_cntrl(l) = 0.
1536      ENDDO
1537       tab_cntrl(1)  = FLOAT(iim)
1538       tab_cntrl(2)  = FLOAT(jjm)
1539       tab_cntrl(3)  = FLOAT(llm)
1540       tab_cntrl(4)  = FLOAT(day_ref)
1541       tab_cntrl(5)  = FLOAT(annee_ref)
1542       tab_cntrl(6)  = rad
1543       tab_cntrl(7)  = omeg
1544       tab_cntrl(8)  = g
1545       tab_cntrl(9)  = cpp
1546       tab_cntrl(10) = kappa
1547       tab_cntrl(11) = daysec
1548       tab_cntrl(12) = dtvr
1549!       tab_cntrl(13) = etot0
1550!       tab_cntrl(14) = ptot0
1551!       tab_cntrl(15) = ztot0
1552!       tab_cntrl(16) = stot0
1553!       tab_cntrl(17) = ang0
1554!       tab_cntrl(18) = pa
1555!       tab_cntrl(19) = preff
1556!
1557!    .....    parametres  pour le zoom      ......   
1558
1559!       tab_cntrl(20)  = clon
1560!       tab_cntrl(21)  = clat
1561!       tab_cntrl(22)  = grossismx
1562!       tab_cntrl(23)  = grossismy
1563!
1564      IF ( fxyhypb )   THEN
1565       tab_cntrl(24) = 1.
1566!       tab_cntrl(25) = dzoomx
1567!       tab_cntrl(26) = dzoomy
1568       tab_cntrl(27) = 0.
1569!       tab_cntrl(28) = taux
1570!       tab_cntrl(29) = tauy
1571      ELSE
1572       tab_cntrl(24) = 0.
1573!       tab_cntrl(25) = dzoomx
1574!       tab_cntrl(26) = dzoomy
1575       tab_cntrl(27) = 0.
1576       tab_cntrl(28) = 0.
1577       tab_cntrl(29) = 0.
1578       IF( ysinus )  tab_cntrl(27) = 1.
1579      ENDIF
1580!Al1 iday_end -> day_end
1581       tab_cntrl(30) = FLOAT(day_end)
1582       tab_cntrl(31) = FLOAT(itau_dyn + itaufin)
1583!
1584      DO pass=1,2
1585      CALL put_var(pass,"controle","Param. de controle Dyn1D",tab_cntrl)
1586!
1587
1588!  Ecriture/extension de la coordonnee temps
1589
1590
1591!  Ecriture des champs
1592!
1593      CALL put_field(pass,"plev","p interfaces sauf la nulle",plev)
1594      CALL put_field(pass,"play","",play)
1595      CALL put_field(pass,"phi","geopotentielle",phi)
1596      CALL put_field(pass,"phis","geopotentiell de surface",phis)
1597      CALL put_field(pass,"presnivs","",presnivs)
1598      CALL put_field(pass,"ucov","",ucov)
1599      CALL put_field(pass,"vcov","",vcov)
1600      CALL put_field(pass,"temp","",temp)
1601      CALL put_field(pass,"omega2","",omega2)
1602
1603      Do iq=1,nqtot
1604        CALL put_field(pass,"q"//nmq(iq),"eau vap ou condens et traceurs",           &
1605     &                                                      q(:,:,iq))
1606      EndDo
1607    IF (pass==1) CALL enddef_restartphy
1608    IF (pass==2) CALL close_restartphy
1609
1610
1611      ENDDO
1612
1613!
1614      RETURN
1615      END
1616      SUBROUTINE gr_fi_dyn(nfield,ngrid,im,jm,pfi,pdyn)
1617      IMPLICIT NONE
1618!=======================================================================
1619!   passage d'un champ de la grille scalaire a la grille physique
1620!=======================================================================
1621 
1622!-----------------------------------------------------------------------
1623!   declarations:
1624!   -------------
1625 
1626      INTEGER im,jm,ngrid,nfield
1627      REAL pdyn(im,jm,nfield)
1628      REAL pfi(ngrid,nfield)
1629 
1630      INTEGER i,j,ifield,ig
1631 
1632!-----------------------------------------------------------------------
1633!   calcul:
1634!   -------
1635 
1636      DO ifield=1,nfield
1637!   traitement des poles
1638         DO i=1,im
1639            pdyn(i,1,ifield)=pfi(1,ifield)
1640            pdyn(i,jm,ifield)=pfi(ngrid,ifield)
1641         ENDDO
1642 
1643!   traitement des point normaux
1644         DO j=2,jm-1
1645            ig=2+(j-2)*(im-1)
1646            CALL SCOPY(im-1,pfi(ig,ifield),1,pdyn(1,j,ifield),1)
1647            pdyn(im,j,ifield)=pdyn(1,j,ifield)
1648         ENDDO
1649      ENDDO
1650 
1651      RETURN
1652      END
1653 
1654 
1655
1656      SUBROUTINE abort_gcm(modname, message, ierr)
1657 
1658      USE IOIPSL
1659!
1660! Stops the simulation cleanly, closing files and printing various
1661! comments
1662!
1663!  Input: modname = name of calling program
1664!         message = stuff to print
1665!         ierr    = severity of situation ( = 0 normal )
1666 
1667      character(len=*) modname
1668      integer ierr
1669      character(len=*) message
1670 
1671      write(*,*) 'in abort_gcm'
1672      call histclo
1673!     call histclo(2)
1674!     call histclo(3)
1675!     call histclo(4)
1676!     call histclo(5)
1677      write(*,*) 'out of histclo'
1678      write(*,*) 'Stopping in ', modname
1679      write(*,*) 'Reason = ',message
1680      call getin_dump
1681!
1682      if (ierr .eq. 0) then
1683        write(*,*) 'Everything is cool'
1684      else
1685        write(*,*) 'Houston, we have a problem ', ierr
1686      endif
1687      STOP
1688      END
1689      REAL FUNCTION fq_sat(kelvin, millibar)
1690!
1691      IMPLICIT none
1692!======================================================================
1693! Autheur(s): Z.X. Li (LMD/CNRS)
1694! Objet: calculer la vapeur d'eau saturante (formule Centre Euro.)
1695!======================================================================
1696! Arguments:
1697! kelvin---input-R: temperature en Kelvin
1698! millibar--input-R: pression en mb
1699!
1700! fq_sat----output-R: vapeur d'eau saturante en kg/kg
1701!======================================================================
1702!
1703      REAL kelvin, millibar
1704!
1705      REAL r2es
1706      PARAMETER (r2es=611.14 *18.0153/28.9644)
1707!
1708      REAL r3les, r3ies, r3es
1709      PARAMETER (R3LES=17.269)
1710      PARAMETER (R3IES=21.875)
1711!
1712      REAL r4les, r4ies, r4es
1713      PARAMETER (R4LES=35.86)
1714      PARAMETER (R4IES=7.66)
1715!
1716      REAL rtt
1717      PARAMETER (rtt=273.16)
1718!
1719      REAL retv
1720      PARAMETER (retv=28.9644/18.0153 - 1.0)
1721!
1722      REAL zqsat
1723      REAL temp, pres
1724!     ------------------------------------------------------------------
1725!
1726!
1727      temp = kelvin
1728      pres = millibar * 100.0
1729!      write(*,*)'kelvin,millibar=',kelvin,millibar
1730!      write(*,*)'temp,pres=',temp,pres
1731!
1732      IF (temp .LE. rtt) THEN
1733         r3es = r3ies
1734         r4es = r4ies
1735      ELSE
1736         r3es = r3les
1737         r4es = r4les
1738      ENDIF
1739!
1740      zqsat=r2es/pres * EXP ( r3es*(temp-rtt) / (temp-r4es) )
1741      zqsat=MIN(0.5,ZQSAT)
1742      zqsat=zqsat/(1.-retv  *zqsat)
1743!
1744      fq_sat = zqsat
1745!
1746      RETURN
1747      END
1748 
1749      SUBROUTINE gr_dyn_fi(nfield,im,jm,ngrid,pdyn,pfi)
1750      IMPLICIT NONE
1751!=======================================================================
1752!   passage d'un champ de la grille scalaire a la grille physique
1753!=======================================================================
1754 
1755!-----------------------------------------------------------------------
1756!   declarations:
1757!   -------------
1758 
1759      INTEGER im,jm,ngrid,nfield
1760      REAL pdyn(im,jm,nfield)
1761      REAL pfi(ngrid,nfield)
1762 
1763      INTEGER j,ifield,ig
1764 
1765!-----------------------------------------------------------------------
1766!   calcul:
1767!   -------
1768 
1769      IF(ngrid.NE.2+(jm-2)*(im-1).AND.ngrid.NE.1)                          &
1770     &    STOP 'probleme de dim'
1771!   traitement des poles
1772      CALL SCOPY(nfield,pdyn,im*jm,pfi,ngrid)
1773      CALL SCOPY(nfield,pdyn(1,jm,1),im*jm,pfi(ngrid,1),ngrid)
1774 
1775!   traitement des point normaux
1776      DO ifield=1,nfield
1777         DO j=2,jm-1
1778            ig=2+(j-2)*(im-1)
1779            CALL SCOPY(im-1,pdyn(1,j,ifield),1,pfi(ig,ifield),1)
1780         ENDDO
1781      ENDDO
1782 
1783      RETURN
1784      END
1785 
1786      SUBROUTINE disvert0(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig)
1787 
1788!    Ancienne version disvert dont on a modifie nom pour utiliser
1789!    le disvert de dyn3d (qui permet d'utiliser grille avec ab,bp imposes)
1790!    (MPL 18092012)
1791!
1792!    Auteur :  P. Le Van .
1793!
1794      IMPLICIT NONE
1795 
1796      include "dimensions.h"
1797      include "paramet.h"
1798!
1799!=======================================================================
1800!
1801!
1802!    s = sigma ** kappa   :  coordonnee  verticale
1803!    dsig(l)            : epaisseur de la couche l ds la coord.  s
1804!    sig(l)             : sigma a l'interface des couches l et l-1
1805!    ds(l)              : distance entre les couches l et l-1 en coord.s
1806!
1807!=======================================================================
1808!
1809      REAL pa,preff
1810      REAL ap(llmp1),bp(llmp1),dpres(llm),nivsigs(llm),nivsig(llmp1)
1811      REAL presnivs(llm)
1812!
1813!   declarations:
1814!   -------------
1815!
1816      REAL sig(llm+1),dsig(llm)
1817!
1818      INTEGER l
1819      REAL snorm
1820      REAL alpha,beta,gama,delta,deltaz,h
1821      INTEGER np,ierr
1822      REAL pi,x
1823 
1824!-----------------------------------------------------------------------
1825!
1826      pi=2.*ASIN(1.)
1827 
1828      OPEN(99,file='sigma.def',status='old',form='formatted',                   &
1829     &   iostat=ierr)
1830 
1831!-----------------------------------------------------------------------
1832!   cas 1 on lit les options dans sigma.def:
1833!   ----------------------------------------
1834 
1835      IF (ierr.eq.0) THEN
1836 
1837      print*,'WARNING!!! on lit les options dans sigma.def'
1838      READ(99,*) deltaz
1839      READ(99,*) h
1840      READ(99,*) beta
1841      READ(99,*) gama
1842      READ(99,*) delta
1843      READ(99,*) np
1844      CLOSE(99)
1845      alpha=deltaz/(llm*h)
1846!
1847 
1848       DO 1  l = 1, llm
1849       dsig(l) = (alpha+(1.-alpha)*exp(-beta*(llm-l)))*                    &
1850     &          ( (tanh(gama*l)/tanh(gama*llm))**np +                      &
1851     &            (1.-l/FLOAT(llm))*delta )
1852   1   CONTINUE
1853 
1854       sig(1)=1.
1855       DO 101 l=1,llm-1
1856          sig(l+1)=sig(l)*(1.-dsig(l))/(1.+dsig(l))
1857101    CONTINUE
1858       sig(llm+1)=0.
1859 
1860       DO 2  l = 1, llm
1861       dsig(l) = sig(l)-sig(l+1)
1862   2   CONTINUE
1863!
1864 
1865      ELSE
1866!-----------------------------------------------------------------------
1867!   cas 2 ancienne discretisation (LMD5...):
1868!   ----------------------------------------
1869 
1870      PRINT*,'WARNING!!! Ancienne discretisation verticale'
1871 
1872      h=7.
1873      snorm  = 0.
1874      DO l = 1, llm
1875         x = 2.*asin(1.) * (FLOAT(l)-0.5) / float(llm+1)
1876         dsig(l) = 1.0 + 7.0 * SIN(x)**2
1877         snorm = snorm + dsig(l)
1878      ENDDO
1879      snorm = 1./snorm
1880      DO l = 1, llm
1881         dsig(l) = dsig(l)*snorm
1882      ENDDO
1883      sig(llm+1) = 0.
1884      DO l = llm, 1, -1
1885         sig(l) = sig(l+1) + dsig(l)
1886      ENDDO
1887 
1888      ENDIF
1889 
1890 
1891      DO l=1,llm
1892        nivsigs(l) = FLOAT(l)
1893      ENDDO
1894 
1895      DO l=1,llmp1
1896        nivsig(l)= FLOAT(l)
1897      ENDDO
1898 
1899!
1900!    ....  Calculs  de ap(l) et de bp(l)  ....
1901!    .........................................
1902!
1903!
1904!   .....  pa et preff sont lus  sur les fichiers start par lectba  .....
1905!
1906 
1907      bp(llmp1) =   0.
1908 
1909      DO l = 1, llm
1910!c
1911!cc    ap(l) = 0.
1912!cc    bp(l) = sig(l)
1913 
1914      bp(l) = EXP( 1. -1./( sig(l)*sig(l)) )
1915      ap(l) = pa * ( sig(l) - bp(l) )
1916!
1917      ENDDO
1918      ap(llmp1) = pa * ( sig(llmp1) - bp(llmp1) )
1919 
1920      PRINT *,' BP '
1921      PRINT *,  bp
1922      PRINT *,' AP '
1923      PRINT *,  ap
1924 
1925      DO l = 1, llm
1926       dpres(l) = bp(l) - bp(l+1)
1927       presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
1928      ENDDO
1929 
1930      PRINT *,' PRESNIVS '
1931      PRINT *,presnivs
1932 
1933      RETURN
1934      END
1935
1936!======================================================================
1937       SUBROUTINE read_tsurf1d(knon,sst_out)
1938
1939! This subroutine specifies the surface temperature to be used in 1D simulations
1940
1941      USE dimphy, ONLY : klon
1942
1943      INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
1944      REAL, DIMENSION(klon), INTENT(OUT)   :: sst_out  ! tsurf used to force the single-column model
1945
1946       INTEGER :: i
1947! COMMON defined in lmdz1d.F:
1948       real ts_cur
1949       common /sst_forcing/ts_cur
1950
1951       DO i = 1, knon
1952        sst_out(i) = ts_cur
1953       ENDDO
1954
1955      END SUBROUTINE read_tsurf1d
1956
1957!===============================================================
1958      subroutine advect_vert(llm,w,dt,q,plev)
1959!===============================================================
1960!   Schema amont pour l'advection verticale en 1D
1961!   w est la vitesse verticale dp/dt en Pa/s
1962!   Traitement en volumes finis
1963!   d / dt ( zm q ) = delta_z ( omega q )
1964!   d / dt ( zm ) = delta_z ( omega )
1965!   avec zm = delta_z ( p )
1966!   si * designe la valeur au pas de temps t+dt
1967!   zm*(l) q*(l) - zm(l) q(l) = w(l+1) q(l+1) - w(l) q(l)
1968!   zm*(l) -zm(l) = w(l+1) - w(l)
1969!   avec w=omega * dt
1970!---------------------------------------------------------------
1971      implicit none
1972! arguments
1973      integer llm
1974      real w(llm+1),q(llm),plev(llm+1),dt
1975
1976! local
1977      integer l
1978      real zwq(llm+1),zm(llm+1),zw(llm+1)
1979      real qold
1980
1981!---------------------------------------------------------------
1982
1983      do l=1,llm
1984         zw(l)=dt*w(l)
1985         zm(l)=plev(l)-plev(l+1)
1986         zwq(l)=q(l)*zw(l)
1987      enddo
1988      zwq(llm+1)=0.
1989      zw(llm+1)=0.
1990 
1991      do l=1,llm
1992         qold=q(l)
1993         q(l)=(q(l)*zm(l)+zwq(l+1)-zwq(l))/(zm(l)+zw(l+1)-zw(l))
1994         print*,'ADV Q ',zm(l),zw(l),zwq(l),qold,q(l)
1995      enddo
1996
1997 
1998      return
1999      end
2000
2001!===============================================================
2002
2003
2004       SUBROUTINE advect_va(llm,omega,d_t_va,d_q_va,d_u_va,d_v_va,              &
2005     &                q,temp,u,v,play)
2006!itlmd
2007!----------------------------------------------------------------------
2008!   Calcul de l'advection verticale (ascendance et subsidence) de
2009!   temperature et d'humidite. Hypothese : ce qui rentre de l'exterieur
2010!   a les memes caracteristiques que l'air de la colonne 1D (WTG) ou
2011!   sans WTG rajouter une advection horizontale
2012!---------------------------------------------------------------------- 
2013        implicit none
2014#include "YOMCST.h"
2015!        argument
2016        integer llm
2017        real  omega(llm+1),d_t_va(llm), d_q_va(llm,3)
2018        real  d_u_va(llm), d_v_va(llm)
2019        real  q(llm,3),temp(llm)
2020        real  u(llm),v(llm)
2021        real  play(llm)
2022! interne
2023        integer l
2024        real alpha,omgdown,omgup
2025
2026      do l= 1,llm
2027       if(l.eq.1) then
2028!si omgup pour la couche 1, alors tendance nulle
2029        omgdown=max(omega(2),0.0)
2030        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
2031        d_t_va(l)= alpha*(omgdown)-omgdown*(temp(l)-temp(l+1))             &
2032     &       /(play(l)-play(l+1))
2033
2034        d_q_va(l,:)= -omgdown*(q(l,:)-q(l+1,:))/(play(l)-play(l+1))             
2035
2036        d_u_va(l)= -omgdown*(u(l)-u(l+1))/(play(l)-play(l+1))             
2037        d_v_va(l)= -omgdown*(v(l)-v(l+1))/(play(l)-play(l+1))             
2038
2039       
2040       elseif(l.eq.llm) then
2041        omgup=min(omega(l),0.0)
2042        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
2043        d_t_va(l)= alpha*(omgup)-                                          &
2044
2045!bug?     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-plev(l))
2046     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-play(l))
2047        d_q_va(l,:)= -omgup*(q(l-1,:)-q(l,:))/(play(l-1)-play(l))
2048        d_u_va(l)= -omgup*(u(l-1)-u(l))/(play(l-1)-play(l))
2049        d_v_va(l)= -omgup*(v(l-1)-v(l))/(play(l-1)-play(l))
2050       
2051       else
2052        omgup=min(omega(l),0.0)
2053        omgdown=max(omega(l+1),0.0)
2054        alpha = rkappa*temp(l)*(1.+q(l,1)*rv/rd)/(play(l)*(1.+q(l,1)))
2055        d_t_va(l)= alpha*(omgup+omgdown)-omgdown*(temp(l)-temp(l+1))       &
2056     &              /(play(l)-play(l+1))-                                  &
2057!bug?     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-plev(l))
2058     &              omgup*(temp(l-1)-temp(l))/(play(l-1)-play(l))
2059!      print*, '  ??? '
2060
2061        d_q_va(l,:)= -omgdown*(q(l,:)-q(l+1,:))                            &
2062     &              /(play(l)-play(l+1))-                                  &
2063     &              omgup*(q(l-1,:)-q(l,:))/(play(l-1)-play(l)) 
2064        d_u_va(l)= -omgdown*(u(l)-u(l+1))                                  &
2065     &              /(play(l)-play(l+1))-                                  &
2066     &              omgup*(u(l-1)-u(l))/(play(l-1)-play(l)) 
2067        d_v_va(l)= -omgdown*(v(l)-v(l+1))                                  &
2068     &              /(play(l)-play(l+1))-                                  &
2069     &              omgup*(v(l-1)-v(l))/(play(l-1)-play(l))
2070       
2071      endif
2072         
2073      enddo
2074!fin itlmd
2075        return
2076        end
2077!       SUBROUTINE lstendH(llm,omega,d_t_va,d_q_va,d_u_va,d_v_va,
2078       SUBROUTINE lstendH(llm,nqtot,omega,d_t_va,d_q_va,                        &
2079     &                q,temp,u,v,play)
2080!itlmd
2081!----------------------------------------------------------------------
2082!   Calcul de l'advection verticale (ascendance et subsidence) de
2083!   temperature et d'humidite. Hypothese : ce qui rentre de l'exterieur
2084!   a les memes caracteristiques que l'air de la colonne 1D (WTG) ou
2085!   sans WTG rajouter une advection horizontale
2086!---------------------------------------------------------------------- 
2087        implicit none
2088#include "YOMCST.h"
2089!        argument
2090        integer llm,nqtot
2091        real  omega(llm+1),d_t_va(llm), d_q_va(llm,nqtot)
2092!        real  d_u_va(llm), d_v_va(llm)
2093        real  q(llm,nqtot),temp(llm)
2094        real  u(llm),v(llm)
2095        real  play(llm)
2096        real cor(llm)
2097!        real dph(llm),dudp(llm),dvdp(llm),dqdp(llm),dtdp(llm)
2098        real dph(llm),dqdp(llm),dtdp(llm)
2099! interne
2100        integer k
2101        real omdn,omup
2102
2103!        dudp=0.
2104!        dvdp=0.
2105        dqdp=0.
2106        dtdp=0.
2107!        d_u_va=0.
2108!        d_v_va=0.
2109
2110      cor(:) = rkappa*temp*(1.+q(:,1)*rv/rd)/(play*(1.+q(:,1)))
2111
2112
2113      do k=2,llm-1
2114
2115       dph  (k-1) = (play()- play(k-1  ))
2116!       dudp (k-1) = (u   ()- u   (k-1  ))/dph(k-1)
2117!       dvdp (k-1) = (v   ()- v   (k-1  ))/dph(k-1)
2118       dqdp (k-1) = (q   (k,1)- q   (k-1,1))/dph(k-1)
2119       dtdp (k-1) = (temp()- temp(k-1  ))/dph(k-1)
2120
2121      enddo
2122
2123!      dudp (  llm  ) = dudp ( llm-1 )
2124!      dvdp (  llm  ) = dvdp ( llm-1 )
2125      dqdp (  llm  ) = dqdp ( llm-1 )
2126      dtdp (  llm  ) = dtdp ( llm-1 )
2127
2128      do k=2,llm-1
2129      omdn=max(0.0,omega(k+1))
2130      omup=min(0.0,omega( k ))
2131
2132!      d_u_va(k)  = -omdn*dudp(k)-omup*dudp(k-1)
2133!      d_v_va(k)  = -omdn*dvdp(k)-omup*dvdp(k-1)
2134      d_q_va(k,1)= -omdn*dqdp(k)-omup*dqdp(k-1)
2135      d_t_va(k)  = -omdn*dtdp(k)-omup*dtdp(k-1)+(omup+omdn)*cor(k)
2136      enddo
2137
2138      omdn=max(0.0,omega( 2 ))
2139      omup=min(0.0,omega(llm))
2140!      d_u_va( 1 )   = -omdn*dudp( 1 )
2141!      d_u_va(llm)   = -omup*dudp(llm)
2142!      d_v_va( 1 )   = -omdn*dvdp( 1 )
2143!      d_v_va(llm)   = -omup*dvdp(llm)
2144      d_q_va( 1 ,1) = -omdn*dqdp( 1 )
2145      d_q_va(llm,1) = -omup*dqdp(llm)
2146      d_t_va( 1 )   = -omdn*dtdp( 1 )+omdn*cor( 1 )
2147      d_t_va(llm)   = -omup*dtdp(llm)!+omup*cor(llm)
2148
2149!      if(abs(rlat(1))>10.) then
2150!     Calculate the tendency due agestrophic motions
2151!      du_age = fcoriolis*(v-vg)
2152!      dv_age = fcoriolis*(ug-u)
2153!      endif
2154
2155!       call writefield_phy('d_t_va',d_t_va,llm)
2156
2157          return
2158         end
2159
2160!======================================================================
2161
2162!  Subroutines for nudging
2163
2164      Subroutine Nudge_RHT_init (paprs,pplay,t,q,t_targ,rh_targ)
2165! ========================================================
2166  USE dimphy
2167
2168  implicit none
2169
2170! ========================================================
2171      REAL paprs(klon,klevp1)
2172      REAL pplay(klon,klev)
2173!
2174!      Variables d'etat
2175      REAL t(klon,klev)
2176      REAL q(klon,klev)
2177!
2178!   Profiles cible
2179      REAL t_targ(klon,klev)
2180      REAL rh_targ(klon,klev)
2181!
2182   INTEGER k,i
2183   REAL zx_qs
2184
2185! Declaration des constantes et des fonctions thermodynamiques
2186!
2187include "YOMCST.h"
2188include "YOETHF.h"
2189!
2190!  ----------------------------------------
2191!  Statement functions
2192include "FCTTRE.h"
2193!  ----------------------------------------
2194!
2195        DO k = 1,klev
2196         DO i = 1,klon
2197           t_targ(i,k) = t(i,k)
2198           IF (t(i,k).LT.RTT) THEN
2199              zx_qs = qsats(t(i,k))/(pplay(i,k))
2200           ELSE
2201              zx_qs = qsatl(t(i,k))/(pplay(i,k))
2202           ENDIF
2203           rh_targ(i,k) = q(i,k)/zx_qs
2204         ENDDO
2205        ENDDO
2206      print *, 't_targ',t_targ
2207      print *, 'rh_targ',rh_targ
2208!
2209!
2210      RETURN
2211      END
2212
2213      Subroutine Nudge_UV_init (paprs,pplay,u,v,u_targ,v_targ)
2214! ========================================================
2215  USE dimphy
2216
2217  implicit none
2218
2219! ========================================================
2220      REAL paprs(klon,klevp1)
2221      REAL pplay(klon,klev)
2222!
2223!      Variables d'etat
2224      REAL u(klon,klev)
2225      REAL v(klon,klev)
2226!
2227!   Profiles cible
2228      REAL u_targ(klon,klev)
2229      REAL v_targ(klon,klev)
2230!
2231   INTEGER k,i
2232!
2233        DO k = 1,klev
2234         DO i = 1,klon
2235           u_targ(i,k) = u(i,k)
2236           v_targ(i,k) = v(i,k)
2237         ENDDO
2238        ENDDO
2239      print *, 'u_targ',u_targ
2240      print *, 'v_targ',v_targ
2241!
2242!
2243      RETURN
2244      END
2245
2246      Subroutine Nudge_RHT (dtime,paprs,pplay,t_targ,rh_targ,t,q,          &
2247     &                      d_t,d_q)
2248! ========================================================
2249  USE dimphy
2250
2251  implicit none
2252
2253! ========================================================
2254      REAL dtime
2255      REAL paprs(klon,klevp1)
2256      REAL pplay(klon,klev)
2257!
2258!      Variables d'etat
2259      REAL t(klon,klev)
2260      REAL q(klon,klev)
2261!
2262! Tendances
2263      REAL d_t(klon,klev)
2264      REAL d_q(klon,klev)
2265!
2266!   Profiles cible
2267      REAL t_targ(klon,klev)
2268      REAL rh_targ(klon,klev)
2269!
2270!   Temps de relaxation
2271      REAL tau
2272!c      DATA tau /3600./
2273!!      DATA tau /5400./
2274      DATA tau /1800./
2275!
2276   INTEGER k,i
2277   REAL zx_qs, rh, tnew, d_rh, rhnew
2278
2279! Declaration des constantes et des fonctions thermodynamiques
2280!
2281include "YOMCST.h"
2282include "YOETHF.h"
2283!
2284!  ----------------------------------------
2285!  Statement functions
2286include "FCTTRE.h"
2287!  ----------------------------------------
2288!
2289        print *,'dtime, tau ',dtime,tau
2290        print *, 't_targ',t_targ
2291        print *, 'rh_targ',rh_targ
2292        print *,'temp ',t
2293        print *,'hum ',q
2294!
2295        DO k = 1,klev
2296         DO i = 1,klon
2297           IF (paprs(i,1)-pplay(i,k) .GT. 10000.) THEN
2298            IF (t(i,k).LT.RTT) THEN
2299               zx_qs = qsats(t(i,k))/(pplay(i,k))
2300            ELSE
2301               zx_qs = qsatl(t(i,k))/(pplay(i,k))
2302            ENDIF
2303            rh = q(i,k)/zx_qs
2304!
2305            d_t(i,k) = d_t(i,k) + 1./tau*(t_targ(i,k)-t(i,k))
2306            d_rh = 1./tau*(rh_targ(i,k)-rh)
2307!
2308            tnew = t(i,k)+d_t(i,k)*dtime
2309!jyg<
2310!   Formule pour q :
2311!                         d_q = (1/tau) [rh_targ*qsat(T_new) - q] 
2312!
2313!  Cette formule remplace d_q = (1/tau) [rh_targ - rh] qsat(T_new)
2314!   qui n'etait pas correcte.
2315!
2316            IF (tnew.LT.RTT) THEN
2317               zx_qs = qsats(tnew)/(pplay(i,k))
2318            ELSE
2319               zx_qs = qsatl(tnew)/(pplay(i,k))
2320            ENDIF
2321!!            d_q(i,k) = d_q(i,k) + d_rh*zx_qs
2322            d_q(i,k) = d_q(i,k) + (1./tau)*(rh_targ(i,k)*zx_qs - q(i,k))
2323            rhnew = (q(i,k)+d_q(i,k)*dtime)/zx_qs
2324!
2325            print *,' k,d_t,rh,d_rh,rhnew,d_q ',    &
2326                      k,d_t(i,k),rh,d_rh,rhnew,d_q(i,k)
2327           ENDIF
2328!
2329         ENDDO
2330        ENDDO
2331!
2332      RETURN
2333      END
2334
2335      Subroutine Nudge_UV (dtime,paprs,pplay,u_targ,v_targ,u,v,          &
2336     &                      d_u,d_v)
2337! ========================================================
2338  USE dimphy
2339
2340  implicit none
2341
2342! ========================================================
2343      REAL dtime
2344      REAL paprs(klon,klevp1)
2345      REAL pplay(klon,klev)
2346!
2347!      Variables d'etat
2348      REAL u(klon,klev)
2349      REAL v(klon,klev)
2350!
2351! Tendances
2352      REAL d_u(klon,klev)
2353      REAL d_v(klon,klev)
2354!
2355!   Profiles cible
2356      REAL u_targ(klon,klev)
2357      REAL v_targ(klon,klev)
2358!
2359!   Temps de relaxation
2360      REAL tau
2361!c      DATA tau /3600./
2362!      DATA tau /5400./
2363       DATA tau /43200./
2364!
2365   INTEGER k,i
2366
2367!
2368        print *,'dtime, tau ',dtime,tau
2369        print *, 'u_targ',u_targ
2370        print *, 'v_targ',v_targ
2371        print *,'zonal velocity ',u
2372        print *,'meridional velocity ',v
2373        DO k = 1,klev
2374         DO i = 1,klon
2375!CR: nudging everywhere
2376!           IF (paprs(i,1)-pplay(i,k) .GT. 10000.) THEN
2377!
2378            d_u(i,k) = d_u(i,k) + 1./tau*(u_targ(i,k)-u(i,k))
2379            d_v(i,k) = d_v(i,k) + 1./tau*(v_targ(i,k)-v(i,k))
2380!
2381            print *,' k,u,d_u,v,d_v ',    &
2382                      k,u(i,k),d_u(i,k),v(i,k),d_v(i,k)
2383!           ENDIF
2384!
2385         ENDDO
2386        ENDDO
2387!
2388      RETURN
2389      END
2390
2391!=====================================================================
2392       SUBROUTINE interp2_case_vertical(play,nlev_cas,plev_prof_cas                                    &
2393     &         ,t_prof_cas,th_prof_cas,thv_prof_cas,thl_prof_cas                                       &
2394     &         ,qv_prof_cas,ql_prof_cas,qi_prof_cas,u_prof_cas,v_prof_cas                              &
2395     &         ,ug_prof_cas,vg_prof_cas,vitw_prof_cas,omega_prof_cas                                   &
2396     &         ,du_prof_cas,hu_prof_cas,vu_prof_cas,dv_prof_cas,hv_prof_cas,vv_prof_cas                &
2397     &         ,dt_prof_cas,ht_prof_cas,vt_prof_cas,dtrad_prof_cas,dq_prof_cas,hq_prof_cas,vq_prof_cas &
2398     &         ,dth_prof_cas,hth_prof_cas,vth_prof_cas                                                 &
2399!
2400     &         ,t_mod_cas,theta_mod_cas,thv_mod_cas,thl_mod_cas                                        &
2401     &         ,qv_mod_cas,ql_mod_cas,qi_mod_cas,u_mod_cas,v_mod_cas                                   &
2402     &         ,ug_mod_cas,vg_mod_cas,w_mod_cas,omega_mod_cas                                          &
2403     &         ,du_mod_cas,hu_mod_cas,vu_mod_cas,dv_mod_cas,hv_mod_cas,vv_mod_cas                      &
2404     &         ,dt_mod_cas,ht_mod_cas,vt_mod_cas,dtrad_mod_cas,dq_mod_cas,hq_mod_cas,vq_mod_cas        &
2405     &         ,dth_mod_cas,hth_mod_cas,vth_mod_cas,mxcalc)
2406 
2407       implicit none
2408 
2409#include "YOMCST.h"
2410#include "dimensions.h"
2411
2412!-------------------------------------------------------------------------
2413! Vertical interpolation of generic case forcing data onto mod_casel levels
2414!-------------------------------------------------------------------------
2415 
2416       integer nlevmax
2417       parameter (nlevmax=41)
2418       integer nlev_cas,mxcalc
2419!       real play(llm), plev_prof(nlevmax) 
2420!       real t_prof(nlevmax),q_prof(nlevmax)
2421!       real u_prof(nlevmax),v_prof(nlevmax), w_prof(nlevmax)
2422!       real ht_prof(nlevmax),vt_prof(nlevmax)
2423!       real hq_prof(nlevmax),vq_prof(nlevmax)
2424 
2425       real play(llm), plev_prof_cas(nlev_cas) 
2426       real t_prof_cas(nlev_cas),th_prof_cas(nlev_cas),thv_prof_cas(nlev_cas),thl_prof_cas(nlev_cas)
2427       real qv_prof_cas(nlev_cas),ql_prof_cas(nlev_cas),qi_prof_cas(nlev_cas)
2428       real u_prof_cas(nlev_cas),v_prof_cas(nlev_cas)
2429       real ug_prof_cas(nlev_cas),vg_prof_cas(nlev_cas), vitw_prof_cas(nlev_cas),omega_prof_cas(nlev_cas)
2430       real du_prof_cas(nlev_cas),hu_prof_cas(nlev_cas),vu_prof_cas(nlev_cas)
2431       real dv_prof_cas(nlev_cas),hv_prof_cas(nlev_cas),vv_prof_cas(nlev_cas)
2432       real dt_prof_cas(nlev_cas),ht_prof_cas(nlev_cas),vt_prof_cas(nlev_cas),dtrad_prof_cas(nlev_cas)
2433       real dth_prof_cas(nlev_cas),hth_prof_cas(nlev_cas),vth_prof_cas(nlev_cas)
2434       real dq_prof_cas(nlev_cas),hq_prof_cas(nlev_cas),vq_prof_cas(nlev_cas)
2435 
2436       real t_mod_cas(llm),theta_mod_cas(llm),thv_mod_cas(llm),thl_mod_cas(llm)
2437       real qv_mod_cas(llm),ql_mod_cas(llm),qi_mod_cas(llm)
2438       real u_mod_cas(llm),v_mod_cas(llm)
2439       real ug_mod_cas(llm),vg_mod_cas(llm), w_mod_cas(llm),omega_mod_cas(llm)
2440       real du_mod_cas(llm),hu_mod_cas(llm),vu_mod_cas(llm)
2441       real dv_mod_cas(llm),hv_mod_cas(llm),vv_mod_cas(llm)
2442       real dt_mod_cas(llm),ht_mod_cas(llm),vt_mod_cas(llm),dtrad_mod_cas(llm)
2443       real dth_mod_cas(llm),hth_mod_cas(llm),vth_mod_cas(llm)
2444       real dq_mod_cas(llm),hq_mod_cas(llm),vq_mod_cas(llm)
2445 
2446       integer l,k,k1,k2
2447       real frac,frac1,frac2,fact
2448 
2449!       do l = 1, llm
2450!       print *,'debut interp2, play=',l,play(l)
2451!       enddo
2452!      do l = 1, nlev_cas
2453!      print *,'debut interp2, plev_prof_cas=',l,play(l),plev_prof_cas(l)
2454!      enddo
2455
2456       do l = 1, llm
2457
2458        if (play(l).ge.plev_prof_cas(nlev_cas)) then
2459 
2460        mxcalc=l
2461!        print *,'debut interp2, mxcalc=',mxcalc
2462         k1=0
2463         k2=0
2464
2465         if (play(l).le.plev_prof_cas(1)) then
2466
2467         do k = 1, nlev_cas-1
2468          if (play(l).le.plev_prof_cas(k).and. play(l).gt.plev_prof_cas(k+1)) then
2469            k1=k
2470            k2=k+1
2471          endif
2472         enddo
2473
2474         if (k1.eq.0 .or. k2.eq.0) then
2475          write(*,*) 'PB! k1, k2 = ',k1,k2
2476          write(*,*) 'l,play(l) = ',l,play(l)/100
2477         do k = 1, nlev_cas-1
2478          write(*,*) 'k,plev_prof_cas(k) = ',k,plev_prof_cas(k)/100
2479         enddo
2480         endif
2481
2482         frac = (plev_prof_cas(k2)-play(l))/(plev_prof_cas(k2)-plev_prof_cas(k1))
2483         t_mod_cas(l)= t_prof_cas(k2) - frac*(t_prof_cas(k2)-t_prof_cas(k1))
2484         theta_mod_cas(l)= th_prof_cas(k2) - frac*(th_prof_cas(k2)-th_prof_cas(k1))
2485         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
2486         thv_mod_cas(l)= thv_prof_cas(k2) - frac*(thv_prof_cas(k2)-thv_prof_cas(k1))
2487         thl_mod_cas(l)= thl_prof_cas(k2) - frac*(thl_prof_cas(k2)-thl_prof_cas(k1))
2488         qv_mod_cas(l)= qv_prof_cas(k2) - frac*(qv_prof_cas(k2)-qv_prof_cas(k1))
2489         ql_mod_cas(l)= ql_prof_cas(k2) - frac*(ql_prof_cas(k2)-ql_prof_cas(k1))
2490         qi_mod_cas(l)= qi_prof_cas(k2) - frac*(qi_prof_cas(k2)-qi_prof_cas(k1))
2491         u_mod_cas(l)= u_prof_cas(k2) - frac*(u_prof_cas(k2)-u_prof_cas(k1))
2492         v_mod_cas(l)= v_prof_cas(k2) - frac*(v_prof_cas(k2)-v_prof_cas(k1))
2493         ug_mod_cas(l)= ug_prof_cas(k2) - frac*(ug_prof_cas(k2)-ug_prof_cas(k1))
2494         vg_mod_cas(l)= vg_prof_cas(k2) - frac*(vg_prof_cas(k2)-vg_prof_cas(k1))
2495         w_mod_cas(l)= vitw_prof_cas(k2) - frac*(vitw_prof_cas(k2)-vitw_prof_cas(k1))
2496         omega_mod_cas(l)= omega_prof_cas(k2) - frac*(omega_prof_cas(k2)-omega_prof_cas(k1))
2497         du_mod_cas(l)= du_prof_cas(k2) - frac*(du_prof_cas(k2)-du_prof_cas(k1))
2498         hu_mod_cas(l)= hu_prof_cas(k2) - frac*(hu_prof_cas(k2)-hu_prof_cas(k1))
2499         vu_mod_cas(l)= vu_prof_cas(k2) - frac*(vu_prof_cas(k2)-vu_prof_cas(k1))
2500         dv_mod_cas(l)= dv_prof_cas(k2) - frac*(dv_prof_cas(k2)-dv_prof_cas(k1))
2501         hv_mod_cas(l)= hv_prof_cas(k2) - frac*(hv_prof_cas(k2)-hv_prof_cas(k1))
2502         vv_mod_cas(l)= vv_prof_cas(k2) - frac*(vv_prof_cas(k2)-vv_prof_cas(k1))
2503         dt_mod_cas(l)= dt_prof_cas(k2) - frac*(dt_prof_cas(k2)-dt_prof_cas(k1))
2504         ht_mod_cas(l)= ht_prof_cas(k2) - frac*(ht_prof_cas(k2)-ht_prof_cas(k1))
2505         vt_mod_cas(l)= vt_prof_cas(k2) - frac*(vt_prof_cas(k2)-vt_prof_cas(k1))
2506         dth_mod_cas(l)= dth_prof_cas(k2) - frac*(dth_prof_cas(k2)-dth_prof_cas(k1))
2507         hth_mod_cas(l)= hth_prof_cas(k2) - frac*(hth_prof_cas(k2)-hth_prof_cas(k1))
2508         vth_mod_cas(l)= vth_prof_cas(k2) - frac*(vth_prof_cas(k2)-vth_prof_cas(k1))
2509         dq_mod_cas(l)= dq_prof_cas(k2) - frac*(dq_prof_cas(k2)-dq_prof_cas(k1))
2510         hq_mod_cas(l)= hq_prof_cas(k2) - frac*(hq_prof_cas(k2)-hq_prof_cas(k1))
2511         vq_mod_cas(l)= vq_prof_cas(k2) - frac*(vq_prof_cas(k2)-vq_prof_cas(k1))
2512         dtrad_mod_cas(l)= dtrad_prof_cas(k2) - frac*(dtrad_prof_cas(k2)-dtrad_prof_cas(k1))
2513     
2514         else !play>plev_prof_cas(1)
2515
2516         k1=1
2517         k2=2
2518         print *,'interp2_vert, k1,k2=',plev_prof_cas(k1),plev_prof_cas(k2)
2519         frac1 = (play(l)-plev_prof_cas(k2))/(plev_prof_cas(k1)-plev_prof_cas(k2))
2520         frac2 = (play(l)-plev_prof_cas(k1))/(plev_prof_cas(k1)-plev_prof_cas(k2))
2521         t_mod_cas(l)= frac1*t_prof_cas(k1) - frac2*t_prof_cas(k2)
2522         theta_mod_cas(l)= frac1*th_prof_cas(k1) - frac2*th_prof_cas(k2)
2523         if(theta_mod_cas(l).NE.0) t_mod_cas(l)= theta_mod_cas(l)*(play(l)/100000.)**(RD/RCPD)
2524         thv_mod_cas(l)= frac1*thv_prof_cas(k1) - frac2*thv_prof_cas(k2)
2525         thl_mod_cas(l)= frac1*thl_prof_cas(k1) - frac2*thl_prof_cas(k2)
2526         qv_mod_cas(l)= frac1*qv_prof_cas(k1) - frac2*qv_prof_cas(k2)
2527         ql_mod_cas(l)= frac1*ql_prof_cas(k1) - frac2*ql_prof_cas(k2)
2528         qi_mod_cas(l)= frac1*qi_prof_cas(k1) - frac2*qi_prof_cas(k2)
2529         u_mod_cas(l)= frac1*u_prof_cas(k1) - frac2*u_prof_cas(k2)
2530         v_mod_cas(l)= frac1*v_prof_cas(k1) - frac2*v_prof_cas(k2)
2531         ug_mod_cas(l)= frac1*ug_prof_cas(k1) - frac2*ug_prof_cas(k2)
2532         vg_mod_cas(l)= frac1*vg_prof_cas(k1) - frac2*vg_prof_cas(k2)
2533         w_mod_cas(l)= frac1*vitw_prof_cas(k1) - frac2*vitw_prof_cas(k2)
2534         omega_mod_cas(l)= frac1*omega_prof_cas(k1) - frac2*omega_prof_cas(k2)
2535         du_mod_cas(l)= frac1*du_prof_cas(k1) - frac2*du_prof_cas(k2)
2536         hu_mod_cas(l)= frac1*hu_prof_cas(k1) - frac2*hu_prof_cas(k2)
2537         vu_mod_cas(l)= frac1*vu_prof_cas(k1) - frac2*vu_prof_cas(k2)
2538         dv_mod_cas(l)= frac1*dv_prof_cas(k1) - frac2*dv_prof_cas(k2)
2539         hv_mod_cas(l)= frac1*hv_prof_cas(k1) - frac2*hv_prof_cas(k2)
2540         vv_mod_cas(l)= frac1*vv_prof_cas(k1) - frac2*vv_prof_cas(k2)
2541         dt_mod_cas(l)= frac1*dt_prof_cas(k1) - frac2*dt_prof_cas(k2)
2542         ht_mod_cas(l)= frac1*ht_prof_cas(k1) - frac2*ht_prof_cas(k2)
2543         vt_mod_cas(l)= frac1*vt_prof_cas(k1) - frac2*vt_prof_cas(k2)
2544         dth_mod_cas(l)= frac1*dth_prof_cas(k1) - frac2*dth_prof_cas(k2)
2545         hth_mod_cas(l)= frac1*hth_prof_cas(k1) - frac2*hth_prof_cas(k2)
2546         vth_mod_cas(l)= frac1*vth_prof_cas(k1) - frac2*vth_prof_cas(k2)
2547         dq_mod_cas(l)= frac1*dq_prof_cas(k1) - frac2*dq_prof_cas(k2)
2548         hq_mod_cas(l)= frac1*hq_prof_cas(k1) - frac2*hq_prof_cas(k2)
2549         vq_mod_cas(l)= frac1*vq_prof_cas(k1) - frac2*vq_prof_cas(k2)
2550         dtrad_mod_cas(l)= frac1*dtrad_prof_cas(k1) - frac2*dtrad_prof_cas(k2)
2551
2552         endif ! play.le.plev_prof_cas(1)
2553
2554        else ! above max altitude of forcing file
2555 
2556!jyg
2557         fact=20.*(plev_prof_cas(nlev_cas)-play(l))/plev_prof_cas(nlev_cas) !jyg
2558         fact = max(fact,0.)                                           !jyg
2559         fact = exp(-fact)                                             !jyg
2560         t_mod_cas(l)= t_prof_cas(nlev_cas)                            !jyg
2561         theta_mod_cas(l)= th_prof_cas(nlev_cas)                       !jyg
2562         thv_mod_cas(l)= thv_prof_cas(nlev_cas)                        !jyg
2563         thl_mod_cas(l)= thl_prof_cas(nlev_cas)                        !jyg
2564         qv_mod_cas(l)= qv_prof_cas(nlev_cas)*fact                     !jyg
2565         ql_mod_cas(l)= ql_prof_cas(nlev_cas)*fact                     !jyg
2566         qi_mod_cas(l)= qi_prof_cas(nlev_cas)*fact                     !jyg
2567         u_mod_cas(l)= u_prof_cas(nlev_cas)*fact                       !jyg
2568         v_mod_cas(l)= v_prof_cas(nlev_cas)*fact                       !jyg
2569         ug_mod_cas(l)= ug_prof_cas(nlev_cas)*fact                     !jyg
2570         vg_mod_cas(l)= vg_prof_cas(nlev_cas)*fact                     !jyg
2571         w_mod_cas(l)= 0.0                                             !jyg
2572         omega_mod_cas(l)= 0.0                                         !jyg
2573         du_mod_cas(l)= du_prof_cas(nlev_cas)*fact
2574         hu_mod_cas(l)= hu_prof_cas(nlev_cas)*fact                     !jyg
2575         vu_mod_cas(l)= vu_prof_cas(nlev_cas)*fact                     !jyg
2576         dv_mod_cas(l)= dv_prof_cas(nlev_cas)*fact
2577         hv_mod_cas(l)= hv_prof_cas(nlev_cas)*fact                     !jyg
2578         vv_mod_cas(l)= vv_prof_cas(nlev_cas)*fact                     !jyg
2579         dt_mod_cas(l)= dt_prof_cas(nlev_cas) 
2580         ht_mod_cas(l)= ht_prof_cas(nlev_cas)                          !jyg
2581         vt_mod_cas(l)= vt_prof_cas(nlev_cas)                          !jyg
2582         dth_mod_cas(l)= dth_prof_cas(nlev_cas) 
2583         hth_mod_cas(l)= hth_prof_cas(nlev_cas)                        !jyg
2584         vth_mod_cas(l)= vth_prof_cas(nlev_cas)                        !jyg
2585         dq_mod_cas(l)= dq_prof_cas(nlev_cas)*fact
2586         hq_mod_cas(l)= hq_prof_cas(nlev_cas)*fact                     !jyg
2587         vq_mod_cas(l)= vq_prof_cas(nlev_cas)*fact                     !jyg
2588         dtrad_mod_cas(l)= dtrad_prof_cas(nlev_cas)*fact               !jyg
2589 
2590        endif ! play
2591 
2592       enddo ! l
2593
2594          return
2595          end
2596!***************************************************************************** 
2597
2598
2599
2600
Note: See TracBrowser for help on using the repository browser.