SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
ol_alloc_atm.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6 SUBROUTINE ol_alloc_atm(KNI,KBANDS,KSCAL)
7 ! #################################################################################
8 !
9 !!
10 !! MODIFICATIONS
11 !! -------------
12 ! 05/2013 B. Decharme : New coupling variables (for AGCM)
13 !-------------------------------------------------------------------------------
14 !
15 USE modd_surf_par, ONLY : xundef
16 
17 USE modd_forc_atm, ONLY: csv ,&! name of all scalar variables
18  xdir_alb ,&! direct albedo for each band
19  xsca_alb ,&! diffuse albedo for each band
20  xemis ,&! emissivity
21  xtsrad ,&! radiative temperature
22  xtsun ,&! solar time (s from midnight)
23  xzs ,&! orography (m)
24  xzref ,&! height of T,q forcing (m)
25  xuref ,&! height of wind forcing (m)
26  xta ,&! air temperature forcing (K)
27  xqa ,&! air specific humidity forcing (kg/m3)
28  xrhoa ,&! air density forcing (kg/m3)
29  xsv ,&! scalar variables
30  xu ,&! zonal wind (m/s)
31  xv ,&! meridian wind (m/s)
32  xdir_sw ,&! direct solar radiation (on horizontal surf.)
33  xsca_sw ,&! diffuse solar radiation (on horizontal surf.)
34  xsw_bands ,&! mean wavelength of each shortwave band (m)
35  xzenith ,&! zenithal angle at t (radian from the vertical)
36  xzenith2 ,&! zenithal angle at t+1 (radian from the vertical)
37  xazim ,&! azimuthal angle (radian from North, clockwise)
38  xlw ,&! longwave radiation (on horizontal surf.)
39  xps ,&! pressure at atmospheric model surface (Pa)
40  xpa ,&! pressure at forcing level (Pa)
41  xco2 ,&! CO2 concentration in the air (kg/kg)
42  xsnow ,&! snow precipitation (kg/m2/s)
43  xrain ,&! liquid precipitation (kg/m2/s)
44  xsfth ,&! flux of heat (W/m2)
45  xsftq ,&! flux of water vapor (kg/m2/s)
46  xsfu ,&! zonal momentum flux (pa)
47  xsfv ,&! meridian momentum flux (pa)
48  xsfco2 ,&! flux of CO2 (kg/m2/s)
49  xsfts ,&! flux of scalar var. (kg/m2/s)
50  xpew_a_coef ,&! implicit coefficients
51  xpew_b_coef ,&! needed if HCOUPLING='I'
52  xpet_a_coef ,&
53  xpeq_a_coef ,&
54  xpet_b_coef ,&
55  xpeq_b_coef ,&
56  xtsurf ,&
57  xz0 ,&
58  xz0h ,&
59  xqsurf
60 !
61 !
62 !
63 USE yomhook ,ONLY : lhook, dr_hook
64 USE parkind1 ,ONLY : jprb
65 !
66 IMPLICIT NONE
67 !
68 !* 0.1 declarations of arguments
69 !
70 INTEGER, INTENT(IN) :: kni ! grid dimension
71 INTEGER, INTENT(IN) :: kbands ! grid dimension
72 INTEGER, INTENT(IN) :: kscal ! grid dimension
73 REAL(KIND=JPRB) :: zhook_handle
74 !
75 !
76 !* 0.2 declarations of local variables
77 !
78 !-------------------------------------------------------------------------------------
79 IF (lhook) CALL dr_hook('OL_ALLOC_ATM',0,zhook_handle)
80 IF (.NOT.ALLOCATED(csv)) ALLOCATE(csv(kscal) )! name of all scalar variables
81 IF (.NOT.ALLOCATED(xdir_alb)) ALLOCATE(xdir_alb(kni,kbands)) ! direct albedo for each band
82 IF (.NOT.ALLOCATED(xsca_alb)) ALLOCATE(xsca_alb(kni,kbands)) ! diffuse albedo for each band
83 IF (.NOT.ALLOCATED(xemis)) ALLOCATE(xemis(kni) )! emissivity
84 IF (.NOT.ALLOCATED(xtsrad)) ALLOCATE(xtsrad(kni) )! radiative temperature
85 IF (.NOT.ALLOCATED(xtsun)) ALLOCATE(xtsun(kni) )! solar time (s from midnight)
86 IF (.NOT.ALLOCATED(xzref)) ALLOCATE(xzref(kni) )! height of T,q forcing (m)
87 IF (.NOT.ALLOCATED(xuref)) ALLOCATE(xuref(kni) )! height of wind forcing (m)
88 IF (.NOT.ALLOCATED(xta)) ALLOCATE(xta(kni) )! air temperature forcing (K)
89 IF (.NOT.ALLOCATED(xqa)) ALLOCATE(xqa(kni) )! air specific humidity forcing (kg/m3)
90 IF (.NOT.ALLOCATED(xzs)) ALLOCATE(xzs(kni) )! orography (m)
91 IF (.NOT.ALLOCATED(xrhoa)) ALLOCATE(xrhoa(kni) )! air density forcing (kg/m3)
92 IF (.NOT.ALLOCATED(xsv)) ALLOCATE(xsv(kni,kscal) ) ! scalar variables
93 IF (.NOT.ALLOCATED(xu)) ALLOCATE(xu(kni) )! zonal wind (m/s)
94 IF (.NOT.ALLOCATED(xv)) ALLOCATE(xv(kni) )! meridian wind (m/s)
95 IF (.NOT.ALLOCATED(xdir_sw)) ALLOCATE(xdir_sw(kni,kbands)) ! direct solar radiation (on horizontal surf.)
96 IF (.NOT.ALLOCATED(xsca_sw)) ALLOCATE(xsca_sw(kni,kbands)) ! diffuse solar radiation (on horizontal surf.)
97 IF (.NOT.ALLOCATED(xsw_bands)) ALLOCATE(xsw_bands(kbands) ) ! mean wavelength of each shortwave band (m)
98 IF (.NOT.ALLOCATED(xzenith)) ALLOCATE(xzenith(kni) )! zenithal angle (radian from the vertical)
99 IF (.NOT.ALLOCATED(xzenith2)) ALLOCATE(xzenith2(kni) )! zenithal angle at t+1(radian from the vertical)
100 IF (.NOT.ALLOCATED(xazim)) ALLOCATE(xazim(kni) )! azimuthal angle (radian from North, clockwise)
101 IF (.NOT.ALLOCATED(xlw)) ALLOCATE(xlw(kni) )! longwave radiation (on horizontal surf.)
102 IF (.NOT.ALLOCATED(xps)) ALLOCATE(xps(kni) )! pressure at atmospheric model surface (Pa)
103 IF (.NOT.ALLOCATED(xpa)) ALLOCATE(xpa(kni) )! pressure at forcing level (Pa)
104 IF (.NOT.ALLOCATED(xco2)) ALLOCATE(xco2(kni) )! CO2 concentration in the air (kg/kg)
105 IF (.NOT.ALLOCATED(xsnow)) ALLOCATE(xsnow(kni) )! snow precipitation (kg/m2/s)
106 IF (.NOT.ALLOCATED(xrain)) ALLOCATE(xrain(kni) )! liquid precipitation (kg/m2/s)
107 IF (.NOT.ALLOCATED(xsfth)) ALLOCATE(xsfth(kni) )! flux of heat (W/m2)
108 IF (.NOT.ALLOCATED(xsftq)) ALLOCATE(xsftq(kni) )! flux of water vapor (kg/m2/s)
109 IF (.NOT.ALLOCATED(xsfu)) ALLOCATE(xsfu(kni) )! zonal momentum flux (pa)
110 IF (.NOT.ALLOCATED(xsfv)) ALLOCATE(xsfv(kni) )! meridian momentum flux (pa)
111 IF (.NOT.ALLOCATED(xsfco2)) ALLOCATE(xsfco2(kni) )! flux of CO2 (kg/m2/s)
112 IF (.NOT.ALLOCATED(xsfts)) ALLOCATE(xsfts(kni,kscal) ) ! flux of scalar var. (kg/m2/s)
113 IF (.NOT.ALLOCATED(xpew_a_coef)) ALLOCATE(xpew_a_coef(kni) )! implicit coefficients
114 IF (.NOT.ALLOCATED(xpew_b_coef)) ALLOCATE(xpew_b_coef(kni) )! needed if HCOUPLING='I'
115 IF (.NOT.ALLOCATED(xpet_a_coef)) ALLOCATE(xpet_a_coef(kni) )
116 IF (.NOT.ALLOCATED(xpeq_a_coef)) ALLOCATE(xpeq_a_coef(kni) )
117 IF (.NOT.ALLOCATED(xpet_b_coef)) ALLOCATE(xpet_b_coef(kni) )
118 IF (.NOT.ALLOCATED(xpeq_b_coef)) ALLOCATE(xpeq_b_coef(kni) )
119 IF (.NOT.ALLOCATED(xtsurf)) ALLOCATE(xtsurf(kni) )
120 IF (.NOT.ALLOCATED(xz0) ) ALLOCATE(xz0(kni) )
121 IF (.NOT.ALLOCATED(xz0h) ) ALLOCATE(xz0h(kni) )
122 IF (.NOT.ALLOCATED(xqsurf)) ALLOCATE(xqsurf(kni) )
123 !
124 IF (SIZE(csv)>=1) csv(1) = '#CO '
125 IF (SIZE(csv)>=2) csv(2) = '#O3 '
126 IF (SIZE(csv)>=3) csv(3) = '#H2O2 '
127 IF (SIZE(csv)>=4) csv(4) = '#NO '
128 IF (SIZE(csv)>=5) csv(5) = '#NO2 '
129 IF (SIZE(csv)>=6) csv(6) = '#NO3 '
130 IF (SIZE(csv)>=7) csv(7) = '#N2O5 '
131 IF (SIZE(csv)>=8) csv(8) = '#HONO '
132 IF (SIZE(csv)>=9) csv(9) = '#HNO3 '
133 IF (SIZE(csv)>=10) csv(10) = '#HNO4 '
134 IF (SIZE(csv)>=11) csv(11) = '#NH3 '
135 IF (SIZE(csv)>=12) csv(12) = '#SO2 '
136 IF (SIZE(csv)>=13) csv(13) = '#SULF '
137 IF (SIZE(csv)>=14) csv(14) = '#OH '
138 IF (SIZE(csv)>=15) csv(15) = '#HO2 '
139 IF (SIZE(csv)>=16) csv(16) = '#CH4 '
140 IF (SIZE(csv)>=17) csv(17) = '#ETH '
141 IF (SIZE(csv)>=18) csv(18) = '#ALKA '
142 IF (SIZE(csv)>=19) csv(19) = '#ALKE '
143 IF (SIZE(csv)>=20) csv(20) = '#BIO '
144 IF (SIZE(csv)>=21) csv(21) = '#ARO '
145 IF (SIZE(csv)>=22) csv(22) = '#HCHO '
146 IF (SIZE(csv)>=23) csv(23) = '#ALD '
147 IF (SIZE(csv)>=24) csv(24) = '#KET '
148 IF (SIZE(csv)>=25) csv(25) = '#CARBO'
149 IF (SIZE(csv)>=26) csv(26) = '#ONIT '
150 IF (SIZE(csv)>=27) csv(27) = '#PAN '
151 IF (SIZE(csv)>=28) csv(28) = '#OP1 '
152 IF (SIZE(csv)>=29) csv(29) = '#OP2 '
153 IF (SIZE(csv)>=30) csv(30) = '#ORA '
154 IF (SIZE(csv)>=31) csv(31) = '#ORA2 '
155 IF (SIZE(csv)>=32) csv(32) = '#MO2 '
156 IF (SIZE(csv)>=33) csv(33) = '#ALKAP'
157 IF (SIZE(csv)>=34) csv(34) = '#ALKEP'
158 IF (SIZE(csv)>=35) csv(35) = '#BIOP '
159 IF (SIZE(csv)>=36) csv(36) = '#PHO '
160 IF (SIZE(csv)>=37) csv(37) = '#ADD '
161 IF (SIZE(csv)>=38) csv(38) = '#AROP '
162 IF (SIZE(csv)>=39) csv(39) = '#CARBO'
163 IF (SIZE(csv)>=40) csv(40) = '#OLN '
164 IF (SIZE(csv)>=41) csv(41) = '#XO2 '
165 IF (SIZE(csv)>=42) csv(42) = '@M0I '
166 IF (SIZE(csv)>=43) csv(43) = '@M0J '
167 IF (SIZE(csv)>=44) csv(44) = '@M6I '
168 IF (SIZE(csv)>=45) csv(45) = '@M6J '
169 IF (SIZE(csv)>=46) csv(46) = '@H2OI'
170 IF (SIZE(csv)>=47) csv(47) = '@H2OJ'
171 IF (SIZE(csv)>=48) csv(48) = '@SO4I'
172 IF (SIZE(csv)>=49) csv(49) = '@SO4J'
173 IF (SIZE(csv)>=50) csv(50) = '@NO3I'
174 IF (SIZE(csv)>=51) csv(51) = '@NO3J'
175 IF (SIZE(csv)>=52) csv(52) = '@NH3I'
176 IF (SIZE(csv)>=53) csv(53) = '@NH3J'
177 IF (SIZE(csv)>=54) csv(54) = '@OCI'
178 IF (SIZE(csv)>=55) csv(55) = '@OCJ'
179 IF (SIZE(csv)>=56) csv(56) = '@BCI'
180 IF (SIZE(csv)>=57) csv(57) = '@BCJ'
181 IF (SIZE(csv)>=58) csv(58) = '@DSTI'
182 IF (SIZE(csv)>=59) csv(59) = '@DSTJ'
183 !
184 !CSV (:) ='UNDEF '! name of all scalar variables
185 xdir_alb(:,:)=xundef ! direct albedo for each band
186 xsca_alb(:,:)=xundef ! diffuse albedo for each band
187 xemis(:)=xundef ! emissivity
188 xtsrad(:)=xundef ! radiative temperature
189 xtsun(:)=xundef ! solar time (s from midnight)
190 xzref(:)=xundef ! height of T,q forcing (m)
191 xuref(:)=xundef ! height of wind forcing (m)
192 xta(:)=xundef ! air temperature forcing (K)
193 xqa(:)=xundef ! air specific humidity forcing (kg/m3)
194 xrhoa(:)=xundef ! air density forcing (kg/m3)
195 xsv(:,:)=xundef ! scalar variables
196 xu(:)=xundef ! zonal wind (m/s)
197 xv(:)=xundef ! meridian wind (m/s)
198 xdir_sw(:,:)=xundef ! direct solar radiation (on horizontal surf.)
199 xsca_sw(:,:)=xundef ! diffuse solar radiation (on horizontal surf.)
200 xsw_bands(:)=xundef ! mean wavelength of each shortwave band (m)
201 xzenith(:)=xundef ! zenithal angle at t (radian from the vertical)
202 xzenith2(:)=xundef ! zenithal angle at t+1 (radian from the vertical)
203 xazim(:)=xundef ! azimuthal angle (radian from North, clockwise)
204 xlw(:)=xundef ! longwave radiation (on horizontal surf.)
205 xps(:)=xundef ! pressure at atmospheric model surface (Pa)
206 xpa(:)=xundef ! pressure at forcing level (Pa)
207 xzs(:)=xundef ! atmospheric model orography (m)
208 xco2(:)=xundef ! CO2 concentration in the air (kg/kg)
209 xsnow(:)=xundef ! snow precipitation (kg/m2/s)
210 xrain(:)=xundef ! liquid precipitation (kg/m2/s)
211 xsfth(:)=xundef ! flux of heat (W/m2)
212 xsftq(:)=xundef ! flux of water vapor (kg/m2/s)
213 xsfu(:)=xundef ! zonal momentum flux (pa)
214 xsfv(:)=xundef ! meridian momentum flux (pa)
215 xsfco2(:)=xundef ! flux of CO2 (kg/m2/s)
216 xsfts(:,:)=xundef ! flux of scalar var. (kg/m2/s)
217 xpew_a_coef(:)=xundef ! implicit coefficients
218 xpew_b_coef(:)=xundef ! needed if HCOUPLING='I'
219 xpet_a_coef(:)=xundef
220 xpeq_a_coef(:)=xundef
221 xpet_b_coef(:)=xundef
222 xpeq_b_coef(:)=xundef
223 xtsurf(:)=xundef ! effective temperature (K)
224 xz0(:)=xundef ! surface roughness length for momentum (m)
225 xz0h(:)=xundef ! surface roughness length for heat (m)
226 xqsurf(:)=xundef ! specific humidity at surface (kg/kg)
227 !
228 IF (lhook) CALL dr_hook('OL_ALLOC_ATM',1,zhook_handle)
229 
230 END SUBROUTINE ol_alloc_atm
subroutine ol_alloc_atm(KNI, KBANDS, KSCAL)
Definition: ol_alloc_atm.F90:6