LMDZ
suinit.F90
Go to the documentation of this file.
1 SUBROUTINE 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 
41 USE parkind1 ,ONLY : jpim ,jprb
42 !#include "tsmbkind.h"
43 
44 USE pardim, ONLY : jpmxle
45 USE yomct0b , ONLY : lecmwf
46 USE yomrip , ONLY : nindat ,nsssss
47 USE yomdim
48 USE yomdphy
49 ! MPL 29042010: NDLNPR,RHYDR0 non initialises et pour ne pas mettre tout sudyn.F90
50 USE 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
54 USE yomgem , ONLY : vdela , vdelb ,vc ,nloen ,nloeng ,ngptot
55 USE yomsta , ONLY : stz ,stpreh ,stpre ,stphi ,sttem ,stden
56 USE yoeaerd , ONLY : cvdaes ,cvdael ,cvdaeu ,cvdaed
57 USE yoeovlp , ONLY : ra1ovlp
58 USE yoecld , ONLY : ceta
59 USE yoecnd , ONLY : cevapcu
60 USE yomtoph , ONLY : rmesou ,rmesot ,rmesoq
61 USE yomgc , ONLY : gemu ,gelam ,gelat ,geclo ,geslo ,gm ,gaw
62 
63 
64 IMPLICIT NONE
65 LOGICAL LLTRACE, LLDEBUG
66 integer klon,klev
67 CHARACTER*200 CFICP
68 CHARACTER*200 CFLUX
69 CHARACTER*200 CLIST
70 CHARACTER*200 CFDDH
71 CHARACTER*80 CNMEXP
72 
73 
74 lltrace=.true.
75 lldebug=.true.
76 
77 ! ------------------------
78 ! * READ NAMELISTS.
79 ! ------------------------
80 
81 !----------------------------------------------------------------
82 ! Elements indispensables de SUNAM pour faire tourner RRTM dans LMDZ
83 !-------------------------------------------------------------------
84 cficp='Profile'
85 cflux='Output'
86 clist='Listing'
87 cfddh='DHFDL'
88 cnmexp='SCM'
89 tstep=450
90 ! MPL 29042010 - RHYDR0 - upper boundary contition for hydrostatic
91 rhydr0=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,
95 ndlnpr=0
96 print *,'SUINIT: RHYDR0 NDLNPR',rhydr0,ndlnpr
97 
98 !----------------------------------------------------------------
99 ! Elements indispensables de SUDIM pour faire tourner RRTM dans LMDZ
100 !-------------------------------------------------------------------
101 ndlon=klon
102 nflevg=klev
103 nproma=klon
104 
105 !-------------------------------------------------------------------
106 !JV Initialize constants
107 ! ---------------------
108 !JV
109 IF (lltrace) WRITE(*,*) " coucou SUINIT : avant SUCST"
110 WRITE(*,fmt='('' ---------------- '')')
111 WRITE(*,fmt='('' SUCST : '')')
112 WRITE(*,fmt='('' ---------------- '')')
113 nindat=20090408 !!!!! A REVOIR (MPL)
114 nsssss=0 ! LMDZ demarre tjrs a 00h -- MPL 15.04.09
115 CALL sucst(6,nindat,nsssss,1)
116 print *,'SUINIT: NINDAT, NSSSSS',nindat, nsssss
117 
118 IF (lldebug) THEN
119 WRITE(*,fmt='('' SUINIT / apres : SUCST '')')
120 ENDIF
121 
122 
123 ! ------------------------
124 ! * ALLOCATES RECUPERES DE SUALLO
125 ! ------------------------
126 ALLOCATE(vdela(max(jpmxle,nflevg)))
127 ALLOCATE(vdelb(max(jpmxle,nflevg)))
128 ALLOCATE( vc(nflevg) )
129 ALLOCATE( nloen(nproma) )
130 ALLOCATE( nloeng(nproma) )
131 ALLOCATE( stz(nflevg) )
132 ALLOCATE( cvdaes(nflevg+1))
133 ALLOCATE( cvdael(nflevg+1))
134 ALLOCATE( cvdaeu(nflevg+1))
135 ALLOCATE( cvdaed(nflevg+1))
136 ALLOCATE(ra1ovlp(nflevg))
137 
138 ALLOCATE(stpreh(0:nflevg)) ! Nouvel ajout MPL 22062010
139 ALLOCATE(stpre(nflevg))
140 ALLOCATE(stphi(nflevg))
141 ALLOCATE(sttem(nflevg))
142 ALLOCATE(stden(nflevg))
143 
144 ALLOCATE(ceta(nflevg)) ! Nouvel ajout MPL 28062010
145 ALLOCATE(cevapcu(nflevg))
146 ALLOCATE(rmesou(nflevg))
147 ALLOCATE(rmesot(nflevg))
148 ALLOCATE(rmesoq(nflevg))
149 
150 ! ------------------------
151 ! * ALLOCATES RECUPERES DE SUGEM2
152 ! ------------------------
153 
154 ALLOCATE(gemu(ngptot)) ! Nouvel ajout MPL 28062010
155 ALLOCATE(gelam(ngptot))
156 ALLOCATE(gelat(ngptot))
157 ALLOCATE(geclo(ngptot))
158 ALLOCATE(geslo(ngptot))
159 ALLOCATE(gm(ngptot))
160 ALLOCATE(gaw(ngptot))
161 !
162 ! ------------------------------------------------------------------
163 
164 END SUBROUTINE suinit
real(kind=jprb), dimension(:), allocatable gaw
Definition: yomgc.F90:60
real(kind=jprb), dimension(:), allocatable geslo
Definition: yomgc.F90:45
integer(kind=jpim), dimension(:), allocatable, target nloeng
Definition: yomgem.F90:102
real(kind=jprb), dimension(:), allocatable stpre
Definition: yomsta.F90:44
real(kind=jprb), dimension(:), allocatable cevapcu
Definition: yoecnd.F90:10
real(kind=jprb), dimension(:), allocatable rmesot
Definition: yomtoph.F90:44
real(kind=jprb), dimension(:), allocatable stden
Definition: yomsta.F90:47
integer(kind=jpim) nsssss
Definition: yomrip.F90:71
real(kind=jprb), dimension(:), allocatable sttem
Definition: yomsta.F90:46
integer(kind=jpim) nproma
Definition: yomdim.F90:87
real(kind=jprb) rhydr0
Definition: yomdyn.F90:290
integer(kind=jpim) ndlon
Definition: yomdim.F90:79
real(kind=jprb), dimension(:), allocatable cvdaes
Definition: yoeaerd.F90:13
integer(kind=jpim) nflevg
Definition: yomdim.F90:112
real(kind=jprb), dimension(:), allocatable gemu
Definition: yomgc.F90:40
real(kind=jprb), dimension(:), allocatable gelam
Definition: yomgc.F90:42
Definition: yomgc.F90:1
subroutine sucst(KULOUT, KDAT, KSSS, KPRINTLEV)
Definition: sucst.F90:2
Definition: yomgem.F90:1
integer(kind=jpim) ngptot
Definition: yomgem.F90:19
real(kind=jprb), dimension(:), allocatable stphi
Definition: yomsta.F90:45
logical lecmwf
Definition: yomct0b.F90:15
Definition: yomsta.F90:1
real(kind=jprb), dimension(:), allocatable ceta
Definition: yoecld.F90:13
integer, parameter jprb
Definition: parkind1.F90:31
real(kind=jprb), dimension(:), allocatable vdelb
Definition: yomgem.F90:171
real(kind=jprb), dimension(:), allocatable vdela
Definition: yomgem.F90:172
real(kind=jprb), dimension(:), allocatable cvdael
Definition: yoeaerd.F90:14
real(kind=jprb), dimension(:), allocatable cvdaed
Definition: yoeaerd.F90:16
Definition: yomdim.F90:1
subroutine suinit(klon, klev)
Definition: suinit.F90:2
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
integer(kind=jpim), dimension(:), allocatable nloen
Definition: yomgem.F90:101
integer(kind=jpim), parameter jpmxle
Definition: pardim.F90:18
real(kind=jprb), dimension(:), allocatable ra1ovlp
Definition: yoeovlp.F90:13
real(kind=jprb), dimension(:), allocatable gm
Definition: yomgc.F90:46
real(kind=jprb) tstep
Definition: yomdyn.F90:25
Definition: yoecld.F90:1
Definition: yomrip.F90:1
Definition: yomdyn.F90:1
real(kind=jprb), dimension(:), allocatable geclo
Definition: yomgc.F90:44
Definition: yoecnd.F90:1
integer, parameter jpim
Definition: parkind1.F90:13
real(kind=jprb), dimension(:), allocatable stpreh
Definition: yomsta.F90:43
integer(kind=jpim) ndlnpr
Definition: yomdyn.F90:258
Definition: pardim.F90:1
real(kind=jprb), dimension(:), allocatable rmesou
Definition: yomtoph.F90:43
real(kind=jprb), dimension(:), allocatable stz
Definition: yomsta.F90:48
real(kind=jprb), dimension(:), allocatable cvdaeu
Definition: yoeaerd.F90:15
integer(kind=jpim) nindat
Definition: yomrip.F90:70
real(kind=jprb), dimension(:), allocatable vc
Definition: yomgem.F90:170
real(kind=jprb), dimension(:), allocatable gelat
Definition: yomgc.F90:43
real(kind=jprb), dimension(:), allocatable rmesoq
Definition: yomtoph.F90:45