source: LMDZ6/trunk/libf/phylmd/rrtm/suinit.F90 @ 3956

Last change on this file since 3956 was 3435, checked in by Laurent Fairhead, 5 years ago

"Historic" :-) commit merging the physics branch used for DYNAMICO with the LMDZ trunk.
The same physics branch can now be used seamlessly with the traditional lon-lat LMDZ
dynamical core and DYNAMICO.
Testing consisted in running a lon-lat LMDZ bucket simulation with the NPv6.1 physics package
with the original trunk sources and the merged sources. Tests were succesful in the sense that
numeric continuity was preserved in the restart files from both simulation. Further tests
included running both versions of the physics codes for one year in a LMDZOR setting in which
the restart files also came out identical.

Caution:

  • as the physics package now manages unstructured grids, grid information needs to be transmitted

to the surface scheme ORCHIDEE. This means that the interface defined in surf_land_orchidee_mod.F90
is only compatible with ORCHIDEE version orchidee2.1 and later versions. If previous versions of
ORCHIDEE need to be used, the CPP key ORCHIDEE_NOUNSTRUCT needs to be set at compilation time.
This is done automatically if makelmdz/makelmdz_fcm are called with the veget orchidee2.0 switch

  • due to a limitation in XIOS, the time at which limit conditions will be read in by DYNAMICO will be

delayed by one physic timestep with respect to the time it is read in by the lon-lat model. This is caused
by the line

IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read

in limit_read_mod.F90

Work still needed on COSP integration and XML files for DYNAMICO

EM, YM, LF

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.5 KB
Line 
1SUBROUTINE SUINIT(klon,klev)
2#ifdef DOC
3
4!     **** *SUINIT* - SCM initialization.
5
6!     Purpose.
7!     --------
8
9!     **   Interface.
10!     ----------
11
12!     Explicit arguments :    None.
13!     --------------------
14
15!     Implicit arguments :    None.
16!     --------------------
17
18!     Method.
19!     -------
20
21!     Externals.   None.
22!     ----------
23
24!     Reference.
25!     ----------
26
27!     Author.
28!     -------
29!     Eric Bazile, Francois Bouyssel et Jean-Marcel Piriou
30
31!     Modifications.
32!     --------------
33!     Original :97-02-01
34!               Jozef Vivoda, SHMI: calling sequence as in 3D model
35!                                   and ECMWF setup
36!     2001-11-27 P. Marquet : several printout on listing (NULOUT=15)
37
38!     ------------------------------------------------------------------
39#endif
40
41USE PARKIND1  ,ONLY : JPIM     ,JPRB
42!#include "tsmbkind.h"
43
44USE PARDIM, ONLY : JPMXLE
45USE YOMCT0B  , ONLY : LECMWF
46USE YOMRIP   , ONLY : NINDAT   ,NSSSSS
47USE YOMDIM 
48USE YOMDPHY 
49! MPL 29042010: NDLNPR,RHYDR0 non initialises et pour ne pas mettre tout sudyn.F90
50USE YOMDYN  , ONLY : TSTEP , NDLNPR , RHYDR0        ! MPL 29042010
51!USE YOMEVOL  , ONLY : TECH     ,FREQFS   ,FREQFE   , FREQDDH
52!USE YOMCT0   , ONLY : LFROG
53! quelques ajouts qui viennent de suallo
54USE YOMGEM   , ONLY : VDELA    , VDELB   ,VC       ,NLOEN    ,NLOENG  ,NGPTOT
55USE YOMSTA   , ONLY : STZ      ,STPREH   ,STPRE    ,STPHI    ,STTEM   ,STDEN
56USE YOEAERD  , ONLY : CVDAES   ,CVDAEL   ,CVDAEU   ,CVDAED
57USE YOEOVLP  , ONLY : RA1OVLP
58USE YOECLD   , ONLY : CETA
59USE YOECND   , ONLY : CEVAPCU
60USE YOMTOPH  , ONLY : RMESOU   ,RMESOT   ,RMESOQ
61USE YOMGC    , ONLY : GEMU     ,GELAM    ,GELAT    ,GECLO    ,GESLO    ,GM       ,GAW
62
63
64IMPLICIT NONE
65LOGICAL LLTRACE, LLDEBUG
66integer klon,klev
67CHARACTER*200 CFICP
68CHARACTER*200 CFLUX
69CHARACTER*200 CLIST
70CHARACTER*200 CFDDH
71CHARACTER*80 CNMEXP
72
73
74LLTRACE=.TRUE.
75LLDEBUG=.TRUE.
76
77!     ------------------------
78!     *    READ NAMELISTS.
79!     ------------------------
80
81!----------------------------------------------------------------
82! Elements indispensables de SUNAM pour faire tourner RRTM dans LMDZ
83!-------------------------------------------------------------------
84CFICP='Profile'
85CFLUX='Output'
86CLIST='Listing'
87CFDDH='DHFDL'
88CNMEXP='SCM'
89TSTEP=450
90! MPL 29042010 - RHYDR0 - upper boundary contition for hydrostatic
91RHYDR0=1._JPRB
92! MPL 29042010
93! NDLNPR : NDLNPR=0: conventional formulation of delta, i.e. ln(P(l)/P(l-1)).
94!          NDLNPR=1: formulation of delta used in non hydrostatic model,
95NDLNPR=0
96print *,'SUINIT: RHYDR0 NDLNPR',RHYDR0,NDLNPR
97
98!----------------------------------------------------------------
99! Elements indispensables de SUDIM pour faire tourner RRTM dans LMDZ
100!-------------------------------------------------------------------
101NDLON=klon
102NFLEVG=klev
103NPROMA=klon
104
105!-------------------------------------------------------------------
106!JV    Initialize constants
107!     ---------------------
108!JV
109IF (LLTRACE)  WRITE(*,*) " coucou SUINIT : avant SUCST"
110WRITE(*,FMT='('' ---------------- '')')
111WRITE(*,FMT='(''     SUCST : '')')
112WRITE(*,FMT='('' ---------------- '')')
113NINDAT=20090408      !!!!! A REVOIR (MPL)
114NSSSSS=0  ! LMDZ demarre tjrs a 00h -- MPL 15.04.09
115CALL SUCST(6,NINDAT,NSSSSS,1)
116print *,'SUINIT: NINDAT, NSSSSS',NINDAT, NSSSSS
117
118IF (LLDEBUG) THEN
119WRITE(*,FMT='(''  SUINIT / apres : SUCST '')')
120ENDIF
121
122
123!     ------------------------
124!     *    ALLOCATES RECUPERES DE SUALLO
125!     ------------------------
126ALLOCATE(VDELA  (MAX(JPMXLE,NFLEVG)))
127ALLOCATE(VDELB  (MAX(JPMXLE,NFLEVG)))
128VDELB = 0  !ym missing init
129ALLOCATE( VC      (NFLEVG) )
130VC = 0    !ym missing init
131ALLOCATE( NLOEN   (NPROMA) )
132ALLOCATE( NLOENG   (NPROMA) )
133ALLOCATE( STZ     (NFLEVG) )
134ALLOCATE( CVDAES  (NFLEVG+1))
135ALLOCATE( CVDAEL  (NFLEVG+1))
136ALLOCATE( CVDAEU  (NFLEVG+1))
137ALLOCATE( CVDAED  (NFLEVG+1))
138ALLOCATE(RA1OVLP(NFLEVG))
139
140ALLOCATE(STPREH(0:NFLEVG)) ! Nouvel ajout MPL 22062010
141ALLOCATE(STPRE(NFLEVG))
142ALLOCATE(STPHI(NFLEVG))
143ALLOCATE(STTEM(NFLEVG))
144ALLOCATE(STDEN(NFLEVG))
145
146ALLOCATE(CETA(NFLEVG))    ! Nouvel ajout MPL 28062010
147ALLOCATE(CEVAPCU(NFLEVG))
148ALLOCATE(RMESOU(NFLEVG))
149ALLOCATE(RMESOT(NFLEVG))
150ALLOCATE(RMESOQ(NFLEVG))
151
152!     ------------------------
153!     *    ALLOCATES RECUPERES DE SUGEM2
154!     ------------------------
155
156ALLOCATE(GEMU   (NGPTOT)) ! Nouvel ajout MPL 28062010
157ALLOCATE(GELAM  (NGPTOT))
158ALLOCATE(GELAT  (NGPTOT))
159ALLOCATE(GECLO  (NGPTOT))
160ALLOCATE(GESLO  (NGPTOT))
161ALLOCATE(GM     (NGPTOT))
162ALLOCATE(GAW    (NGPTOT))
163
164!     ------------------------------------------------------------------
165
166END SUBROUTINE SUINIT
Note: See TracBrowser for help on using the repository browser.