1 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
2 | ! |
---|
3 | ! Module pour construir et detruire les variables "cospIN", "cospstateIN" et "cospOUT" |
---|
4 | ! |
---|
5 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
6 | |
---|
7 | MODULE LMDZ_COSP_CONSTRUCT_DESTROY_MOD |
---|
8 | |
---|
9 | use cosp_kinds, only: wp |
---|
10 | use mod_cosp, only: cosp_optical_inputs,cosp_column_inputs,cosp_outputs |
---|
11 | use lmdz_cosp_read_outputkeys, only: cosp_config |
---|
12 | |
---|
13 | USE mod_cosp_config, only : R_UNDEF, CLOUDSAT_DBZE_BINS, SR_BINS, PARASOL_NREFL, & |
---|
14 | LIDAR_NTEMP, LIDAR_NCAT, LIDAR_NTYPE, & |
---|
15 | numMODISReffIceBins,reffICE_binCenters, & |
---|
16 | numMODISReffLiqBins, reffLIQ_binCenters, & |
---|
17 | numISCCPTauBins,numISCCPPresBins, & |
---|
18 | numMISRTauBins,numMISRHgtBins, & |
---|
19 | numModisTauBins,numMODISPresBins |
---|
20 | |
---|
21 | implicit none |
---|
22 | |
---|
23 | contains |
---|
24 | |
---|
25 | |
---|
26 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
27 | ! SUBROUTINE construct_cospIN |
---|
28 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
29 | subroutine construct_cospIN(cfg,npoints,ncolumns,nlevels,y) |
---|
30 | ! Inputs |
---|
31 | integer,intent(in) :: & |
---|
32 | npoints, & ! Number of horizontal gridpoints |
---|
33 | ncolumns, & ! Number of subcolumns |
---|
34 | nlevels ! Number of vertical levels |
---|
35 | |
---|
36 | type(cosp_config),intent(in) :: & |
---|
37 | cfg ! COSP output config (logical keys) |
---|
38 | |
---|
39 | ! Outputs |
---|
40 | type(cosp_optical_inputs),intent(out) :: y |
---|
41 | |
---|
42 | ! Dimensions |
---|
43 | y%Npoints = Npoints |
---|
44 | y%Ncolumns = Ncolumns |
---|
45 | y%Nlevels = Nlevels |
---|
46 | y%Npart = 4 |
---|
47 | y%Nrefl = PARASOL_NREFL |
---|
48 | allocate(y%frac_out(npoints, ncolumns,nlevels)) |
---|
49 | |
---|
50 | if (cfg%Lmodis .or. cfg%Lmisr .or. cfg%Lisccp) then |
---|
51 | allocate(y%tau_067(npoints, ncolumns,nlevels),& |
---|
52 | y%emiss_11(npoints, ncolumns,nlevels)) |
---|
53 | endif |
---|
54 | if (cfg%Lcalipso) then |
---|
55 | allocate(y%betatot_calipso(npoints, ncolumns,nlevels),& |
---|
56 | y%betatot_ice_calipso(npoints, ncolumns,nlevels),& |
---|
57 | y%betatot_liq_calipso(npoints, ncolumns,nlevels),& |
---|
58 | y%tautot_calipso(npoints, ncolumns,nlevels),& |
---|
59 | y%tautot_ice_calipso(npoints, ncolumns,nlevels),& |
---|
60 | y%tautot_liq_calipso(npoints, ncolumns,nlevels),& |
---|
61 | y%beta_mol_calipso(npoints, nlevels),& |
---|
62 | y%tau_mol_calipso(npoints, nlevels),& |
---|
63 | y%tautot_S_ice(npoints, ncolumns ),& |
---|
64 | y%tautot_S_liq(npoints, ncolumns )) |
---|
65 | endif |
---|
66 | |
---|
67 | if (cfg%LgrLidar532) then |
---|
68 | allocate(y%beta_mol_grLidar532(npoints, nlevels),& |
---|
69 | y%betatot_grLidar532(npoints, ncolumns,nlevels),& |
---|
70 | y%tau_mol_grLidar532(npoints, nlevels),& |
---|
71 | y%tautot_grLidar532(npoints, ncolumns,nlevels)) |
---|
72 | endif |
---|
73 | |
---|
74 | if (cfg%Latlid) then |
---|
75 | allocate(y%beta_mol_atlid(npoints, nlevels),& |
---|
76 | y%betatot_atlid(npoints, ncolumns,nlevels),& |
---|
77 | y%tau_mol_atlid(npoints, nlevels),& |
---|
78 | y%tautot_atlid(npoints, ncolumns,nlevels)) |
---|
79 | endif |
---|
80 | |
---|
81 | if (cfg%Lcloudsat) then |
---|
82 | allocate(y%z_vol_cloudsat(npoints, ncolumns,nlevels),& |
---|
83 | y%kr_vol_cloudsat(npoints, ncolumns,nlevels),& |
---|
84 | y%g_vol_cloudsat(npoints, ncolumns,nlevels),& |
---|
85 | y%fracPrecipIce(npoints, ncolumns)) |
---|
86 | endif |
---|
87 | if (cfg%Lmodis) then |
---|
88 | allocate(y%fracLiq(npoints, ncolumns,nlevels),& |
---|
89 | y%asym(npoints, ncolumns,nlevels),& |
---|
90 | y%ss_alb(npoints, ncolumns,nlevels)) |
---|
91 | endif |
---|
92 | |
---|
93 | |
---|
94 | end subroutine construct_cospIN |
---|
95 | |
---|
96 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
97 | ! SUBROUTINE construct_cospstateIN |
---|
98 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
99 | subroutine construct_cospstateIN(npoints,nlevels,nchan,y) |
---|
100 | ! Inputs |
---|
101 | integer,intent(in) :: & |
---|
102 | npoints, & ! Number of horizontal gridpoints |
---|
103 | nlevels, & ! Number of vertical levels |
---|
104 | nchan ! Number of channels |
---|
105 | ! Outputs |
---|
106 | type(cosp_column_inputs),intent(out) :: y |
---|
107 | |
---|
108 | allocate(y%sunlit(npoints),y%skt(npoints),y%land(npoints),y%at(npoints,nlevels), & |
---|
109 | y%pfull(npoints,nlevels),y%phalf(npoints,nlevels+1),y%qv(npoints,nlevels), & |
---|
110 | y%o3(npoints,nlevels),y%hgt_matrix(npoints,nlevels),y%u_sfc(npoints), & |
---|
111 | y%v_sfc(npoints),y%lat(npoints),y%lon(nPoints),y%emis_sfc(nchan), & |
---|
112 | y%cloudIce(nPoints,nLevels),y%cloudLiq(nPoints,nLevels),y%surfelev(npoints),& |
---|
113 | y%fl_snow(nPoints,nLevels),y%fl_rain(nPoints,nLevels),y%seaice(npoints), & |
---|
114 | y%tca(nPoints,nLevels),y%hgt_matrix_half(npoints,nlevels+1)) |
---|
115 | |
---|
116 | end subroutine construct_cospstateIN |
---|
117 | |
---|
118 | ! ###################################################################################### |
---|
119 | ! SUBROUTINE construct_cosp_outputs |
---|
120 | ! |
---|
121 | ! This subroutine allocates output fields based on input logical flag switches. |
---|
122 | ! ###################################################################################### |
---|
123 | subroutine construct_cosp_outputs(cfg,Npoints,Ncolumns,Nlevels,Nlvgrid,Nchan,x) |
---|
124 | ! Inputs |
---|
125 | integer,intent(in) :: & |
---|
126 | Npoints, & ! Number of sampled points |
---|
127 | Ncolumns, & ! Number of subgrid columns |
---|
128 | Nlevels, & ! Number of model levels |
---|
129 | Nlvgrid, & ! Number of levels in L3 stats computation |
---|
130 | Nchan ! Number of RTTOV channels |
---|
131 | type(cosp_config),intent(in) :: & |
---|
132 | cfg ! COSP output config (logical keys) |
---|
133 | |
---|
134 | ! Outputs |
---|
135 | type(cosp_outputs),intent(out) :: & |
---|
136 | x ! COSP output structure |
---|
137 | |
---|
138 | ! ISCCP simulator outputs |
---|
139 | if (cfg%Lboxtauisccp) allocate(x%isccp_boxtau(Npoints,Ncolumns)) |
---|
140 | if (cfg%Lboxptopisccp) allocate(x%isccp_boxptop(Npoints,Ncolumns)) |
---|
141 | if (cfg%Lclisccp) allocate(x%isccp_fq(Npoints,numISCCPTauBins,numISCCPPresBins)) |
---|
142 | if (cfg%Lcltisccp) allocate(x%isccp_totalcldarea(Npoints)) |
---|
143 | if (cfg%Lpctisccp) allocate(x%isccp_meanptop(Npoints)) |
---|
144 | if (cfg%Ltauisccp) allocate(x%isccp_meantaucld(Npoints)) |
---|
145 | if (cfg%Lmeantbisccp) allocate(x%isccp_meantb(Npoints)) |
---|
146 | if (cfg%Lmeantbclrisccp) allocate(x%isccp_meantbclr(Npoints)) |
---|
147 | if (cfg%Lalbisccp) allocate(x%isccp_meanalbedocld(Npoints)) |
---|
148 | |
---|
149 | ! MISR simulator |
---|
150 | if (cfg%LclMISR) then |
---|
151 | allocate(x%misr_fq(Npoints,numMISRTauBins,numMISRHgtBins)) |
---|
152 | ! *NOTE* These 3 fields are not output, but were part of the v1.4.0 cosp_misr, so |
---|
153 | ! they are still computed. Should probably have a logical to control these |
---|
154 | ! outputs. |
---|
155 | allocate(x%misr_dist_model_layertops(Npoints,numMISRHgtBins)) |
---|
156 | allocate(x%misr_meanztop(Npoints)) |
---|
157 | allocate(x%misr_cldarea(Npoints)) |
---|
158 | endif |
---|
159 | |
---|
160 | ! MODIS simulator |
---|
161 | if (cfg%Lcltmodis) allocate(x%modis_Cloud_Fraction_Total_Mean(Npoints)) |
---|
162 | if (cfg%Lclwmodis) allocate(x%modis_Cloud_Fraction_Water_Mean(Npoints)) |
---|
163 | if (cfg%Lclimodis) allocate(x%modis_Cloud_Fraction_Ice_Mean(Npoints)) |
---|
164 | if (cfg%Lclhmodis) allocate(x%modis_Cloud_Fraction_High_Mean(Npoints)) |
---|
165 | if (cfg%Lclmmodis) allocate(x%modis_Cloud_Fraction_Mid_Mean(Npoints)) |
---|
166 | if (cfg%Lcllmodis) allocate(x%modis_Cloud_Fraction_Low_Mean(Npoints)) |
---|
167 | if (cfg%Ltautmodis) allocate(x%modis_Optical_Thickness_Total_Mean(Npoints)) |
---|
168 | if (cfg%Ltauwmodis) allocate(x%modis_Optical_Thickness_Water_Mean(Npoints)) |
---|
169 | if (cfg%Ltauimodis) allocate(x%modis_Optical_Thickness_Ice_Mean(Npoints)) |
---|
170 | if (cfg%Ltautlogmodis) allocate(x%modis_Optical_Thickness_Total_LogMean(Npoints)) |
---|
171 | if (cfg%Ltauwlogmodis) allocate(x%modis_Optical_Thickness_Water_LogMean(Npoints)) |
---|
172 | if (cfg%Ltauilogmodis) allocate(x%modis_Optical_Thickness_Ice_LogMean(Npoints)) |
---|
173 | if (cfg%Lreffclwmodis) allocate(x%modis_Cloud_Particle_Size_Water_Mean(Npoints)) |
---|
174 | if (cfg%Lreffclimodis) allocate(x%modis_Cloud_Particle_Size_Ice_Mean(Npoints)) |
---|
175 | if (cfg%Lpctmodis) allocate(x%modis_Cloud_Top_Pressure_Total_Mean(Npoints)) |
---|
176 | if (cfg%Llwpmodis) allocate(x%modis_Liquid_Water_Path_Mean(Npoints)) |
---|
177 | if (cfg%Liwpmodis) allocate(x%modis_Ice_Water_Path_Mean(Npoints)) |
---|
178 | if (cfg%Lclmodis) then |
---|
179 | allocate(x%modis_Optical_Thickness_vs_Cloud_Top_Pressure(nPoints,numModisTauBins,numMODISPresBins)) |
---|
180 | allocate(x%modis_Optical_thickness_vs_ReffLIQ(nPoints,numMODISTauBins,numMODISReffLiqBins)) |
---|
181 | allocate(x%modis_Optical_Thickness_vs_ReffICE(nPoints,numMODISTauBins,numMODISReffIceBins)) |
---|
182 | endif |
---|
183 | |
---|
184 | ! LIDAR simulator |
---|
185 | if (cfg%LlidarBetaMol532) allocate(x%calipso_beta_mol(Npoints,Nlevels)) |
---|
186 | if (cfg%Latb532) allocate(x%calipso_beta_tot(Npoints,Ncolumns,Nlevels)) |
---|
187 | if (cfg%LcfadLidarsr532) then |
---|
188 | allocate(x%calipso_srbval(SR_BINS+1)) |
---|
189 | allocate(x%calipso_cfad_sr(Npoints,SR_BINS,Nlvgrid)) |
---|
190 | allocate(x%calipso_betaperp_tot(Npoints,Ncolumns,Nlevels)) |
---|
191 | endif |
---|
192 | if (cfg%Lclcalipso) allocate(x%calipso_lidarcld(Npoints,Nlvgrid)) |
---|
193 | if (cfg%Lclhcalipso .or. cfg%Lclmcalipso .or. cfg%Lcllcalipso .or. cfg%Lcltcalipso) then |
---|
194 | allocate(x%calipso_cldlayer(Npoints,LIDAR_NCAT)) |
---|
195 | endif |
---|
196 | if (cfg%Lclcalipsoice .or. cfg%Lclcalipsoliq .or. cfg%Lclcalipsoun) then |
---|
197 | allocate(x%calipso_lidarcldphase(Npoints,Nlvgrid,6)) |
---|
198 | endif |
---|
199 | if (cfg%Lclcalipsotmp .or. cfg%Lclcalipsotmpliq .or. cfg%Lclcalipsoice .or. & |
---|
200 | cfg%Lclcalipsotmpun .or. cfg%Lclcalipsotmpice) then |
---|
201 | allocate(x%calipso_lidarcldtmp(Npoints,LIDAR_NTEMP,5)) |
---|
202 | endif |
---|
203 | if (cfg%Lcllcalipsoice .or. cfg%Lclmcalipsoice .or. cfg%Lclhcalipsoice .or. & |
---|
204 | cfg%Lcltcalipsoice .or. cfg%Lcllcalipsoliq .or. cfg%Lclmcalipsoliq .or. & |
---|
205 | cfg%Lclhcalipsoliq .or. cfg%Lcltcalipsoliq .or. cfg%Lcllcalipsoun .or. & |
---|
206 | cfg%Lclmcalipsoun .or. cfg%Lclhcalipsoun .or. cfg%Lcltcalipsoun) then |
---|
207 | allocate(x%calipso_cldlayerphase(Npoints,LIDAR_NCAT,6)) |
---|
208 | endif |
---|
209 | if (cfg%Lclopaquecalipso .or. cfg%Lclthincalipso .or. cfg%Lclzopaquecalipso) then |
---|
210 | allocate(x%calipso_cldtype(Npoints,LIDAR_NTYPE)) |
---|
211 | endif |
---|
212 | if (cfg%Lclopaquetemp .or. cfg%Lclthintemp .or. cfg%Lclzopaquetemp) then |
---|
213 | allocate(x%calipso_cldtypetemp(Npoints,LIDAR_NTYPE)) |
---|
214 | endif |
---|
215 | if (cfg%Lclopaquemeanz .or. cfg%Lclthinmeanz) then |
---|
216 | allocate(x%calipso_cldtypemeanz(Npoints,2)) |
---|
217 | endif |
---|
218 | if (cfg%Lclopaquemeanzse .or. cfg%Lclthinmeanzse .or. cfg%Lclzopaquecalipsose) then |
---|
219 | allocate(x%calipso_cldtypemeanzse(Npoints,3)) |
---|
220 | endif |
---|
221 | if (cfg%Lclthinemis) then |
---|
222 | allocate(x%calipso_cldthinemis(Npoints)) |
---|
223 | endif |
---|
224 | if (cfg%Lclcalipsoopaque .or. cfg%Lclcalipsothin .or. cfg%Lclcalipsozopaque .or. & |
---|
225 | cfg%Lclcalipsoopacity) then |
---|
226 | allocate(x%calipso_lidarcldtype(Npoints,Nlvgrid,LIDAR_NTYPE+1)) |
---|
227 | endif |
---|
228 | ! These 2 outputs are part of the calipso output type, but are not controlled by an |
---|
229 | ! logical switch in the output namelist, so if all other fields are on, then allocate |
---|
230 | if (cfg%LlidarBetaMol532 .or. cfg%Latb532 .or. cfg%LcfadLidarsr532 .or. cfg%Lclcalipso .or. & |
---|
231 | cfg%Lclcalipsoice .or. cfg%Lclcalipsoliq .or. cfg%Lclcalipsoun .or. cfg%Lclcalipso2 .or. & |
---|
232 | cfg%Lclhcalipso .or. cfg%Lclmcalipso .or. cfg%Lcllcalipso .or. cfg%Lcltcalipso .or. & |
---|
233 | cfg%Lclcalipsotmp .or. cfg%Lclcalipsoice .or. cfg%Lclcalipsotmpun .or. & |
---|
234 | cfg%Lclcalipsotmpliq .or. cfg%Lcllcalipsoice .or. cfg%Lclmcalipsoice .or. & |
---|
235 | cfg%Lclhcalipsoice .or. cfg%Lcltcalipsoice .or. cfg%Lcllcalipsoliq .or. & |
---|
236 | cfg%Lclmcalipsoliq .or. cfg%Lclhcalipsoliq .or. cfg%Lcltcalipsoliq .or. & |
---|
237 | cfg%Lcllcalipsoun .or. cfg%Lclmcalipsoun .or. cfg%Lclhcalipsoun .or. cfg%Lcltcalipsoun) then |
---|
238 | allocate(x%calipso_tau_tot(Npoints,Ncolumns,Nlevels)) |
---|
239 | allocate(x%calipso_temp_tot(Npoints,Nlevels)) |
---|
240 | endif |
---|
241 | |
---|
242 | ! GROUND LIDAR @ 532NM simulator |
---|
243 | if (cfg%LlidarBetaMol532gr) allocate(x%grLidar532_beta_mol(Npoints,Nlevels)) |
---|
244 | if (cfg%Latb532gr) allocate(x%grLidar532_beta_tot(Npoints,Ncolumns,Nlevels)) |
---|
245 | if (cfg%LcfadLidarsr532gr) then |
---|
246 | allocate(x%grLidar532_srbval(SR_BINS+1)) |
---|
247 | allocate(x%grLidar532_cfad_sr(Npoints,SR_BINS,Nlvgrid)) |
---|
248 | endif |
---|
249 | if (cfg%LclgrLidar532) allocate(x%grLidar532_lidarcld(Npoints,Nlvgrid)) |
---|
250 | if (cfg%LclhgrLidar532 .or. cfg%LclmgrLidar532 .or. cfg%LcllgrLidar532 .or. cfg%LcltgrLidar532) then |
---|
251 | allocate(x%grLidar532_cldlayer(Npoints,LIDAR_NCAT)) |
---|
252 | endif |
---|
253 | |
---|
254 | ! ATLID simulator |
---|
255 | if (cfg%LlidarBetaMol355) allocate(x%atlid_beta_mol(Npoints,Nlevels)) |
---|
256 | if (cfg%Latb355) allocate(x%atlid_beta_tot(Npoints,Ncolumns,Nlevels)) |
---|
257 | if (cfg%LcfadLidarsr355) then |
---|
258 | allocate(x%atlid_srbval(SR_BINS+1)) |
---|
259 | allocate(x%atlid_cfad_sr(Npoints,SR_BINS,Nlvgrid)) |
---|
260 | endif |
---|
261 | if (cfg%Lclatlid) allocate(x%atlid_lidarcld(Npoints,Nlvgrid)) |
---|
262 | if (cfg%Lclhatlid .or. cfg%Lclmatlid .or. cfg%Lcllatlid .or. cfg%Lcltatlid) then |
---|
263 | allocate(x%atlid_cldlayer(Npoints,LIDAR_NCAT)) |
---|
264 | endif |
---|
265 | |
---|
266 | ! PARASOL |
---|
267 | if (cfg%Lparasolrefl) then |
---|
268 | allocate(x%parasolPix_refl(Npoints,Ncolumns,PARASOL_NREFL)) |
---|
269 | allocate(x%parasolGrid_refl(Npoints,PARASOL_NREFL)) |
---|
270 | endif |
---|
271 | |
---|
272 | ! Cloudsat simulator |
---|
273 | if (cfg%Ldbze94) allocate(x%cloudsat_Ze_tot(Npoints,Ncolumns,Nlevels)) |
---|
274 | if (cfg%LcfadDbze94) allocate(x%cloudsat_cfad_ze(Npoints,cloudsat_DBZE_BINS,Nlvgrid)) |
---|
275 | if (cfg%Lptradarflag0 .or. cfg%Lptradarflag1 .or. cfg%Lptradarflag2 .or. cfg%Lptradarflag3 .or. & |
---|
276 | cfg%Lptradarflag4 .or. cfg%Lptradarflag5 .or. cfg%Lptradarflag6 .or. cfg%Lptradarflag7 .or. & |
---|
277 | cfg%Lptradarflag8 .or. cfg%Lptradarflag9) then |
---|
278 | allocate(x%cloudsat_precip_cover(Npoints,cloudsat_DBZE_BINS)) |
---|
279 | endif |
---|
280 | if (cfg%Lradarpia) allocate(x%cloudsat_pia(Npoints)) |
---|
281 | |
---|
282 | ! Combined CALIPSO/CLOUDSAT fields |
---|
283 | if (cfg%Lclcalipso2) allocate(x%lidar_only_freq_cloud(Npoints,Nlvgrid)) |
---|
284 | if (cfg%Lcltlidarradar) allocate(x%radar_lidar_tcc(Npoints)) |
---|
285 | if (cfg%Lcloudsat_tcc) allocate(x%cloudsat_tcc(Npoints)) |
---|
286 | if (cfg%Lcloudsat_tcc2) allocate(x%cloudsat_tcc2(Npoints)) |
---|
287 | |
---|
288 | ! RTTOV |
---|
289 | if (cfg%Ltbrttov) allocate(x%rttov_tbs(Npoints,Nchan)) |
---|
290 | |
---|
291 | end subroutine construct_cosp_outputs |
---|
292 | |
---|
293 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
294 | ! SUBROUTINE destroy_cospIN |
---|
295 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
296 | subroutine destroy_cospIN(y) |
---|
297 | type(cosp_optical_inputs),intent(inout) :: y |
---|
298 | |
---|
299 | if (allocated(y%tau_067)) deallocate(y%tau_067) |
---|
300 | if (allocated(y%emiss_11)) deallocate(y%emiss_11) |
---|
301 | if (allocated(y%frac_out)) deallocate(y%frac_out) |
---|
302 | if (allocated(y%beta_mol_calipso)) deallocate(y%beta_mol_calipso) |
---|
303 | if (allocated(y%tau_mol_calipso)) deallocate(y%tau_mol_calipso) |
---|
304 | if (allocated(y%betatot_calipso)) deallocate(y%betatot_calipso) |
---|
305 | if (allocated(y%betatot_ice_calipso)) deallocate(y%betatot_ice_calipso) |
---|
306 | if (allocated(y%betatot_liq_calipso)) deallocate(y%betatot_liq_calipso) |
---|
307 | if (allocated(y%tautot_calipso)) deallocate(y%tautot_calipso) |
---|
308 | if (allocated(y%tautot_ice_calipso)) deallocate(y%tautot_ice_calipso) |
---|
309 | if (allocated(y%tautot_liq_calipso)) deallocate(y%tautot_liq_calipso) |
---|
310 | if (allocated(y%tautot_S_liq)) deallocate(y%tautot_S_liq) |
---|
311 | if (allocated(y%tautot_S_ice)) deallocate(y%tautot_S_ice) |
---|
312 | if (allocated(y%z_vol_cloudsat)) deallocate(y%z_vol_cloudsat) |
---|
313 | if (allocated(y%kr_vol_cloudsat)) deallocate(y%kr_vol_cloudsat) |
---|
314 | if (allocated(y%g_vol_cloudsat)) deallocate(y%g_vol_cloudsat) |
---|
315 | if (allocated(y%asym)) deallocate(y%asym) |
---|
316 | if (allocated(y%ss_alb)) deallocate(y%ss_alb) |
---|
317 | if (allocated(y%fracLiq)) deallocate(y%fracLiq) |
---|
318 | if (allocated(y%beta_mol_grLidar532)) deallocate(y%beta_mol_grLidar532) |
---|
319 | if (allocated(y%betatot_grLidar532)) deallocate(y%betatot_grLidar532) |
---|
320 | if (allocated(y%tau_mol_grLidar532)) deallocate(y%tau_mol_grLidar532) |
---|
321 | if (allocated(y%tautot_grLidar532)) deallocate(y%tautot_grLidar532) |
---|
322 | if (allocated(y%beta_mol_atlid)) deallocate(y%beta_mol_atlid) |
---|
323 | if (allocated(y%betatot_atlid)) deallocate(y%betatot_atlid) |
---|
324 | if (allocated(y%tau_mol_atlid)) deallocate(y%tau_mol_atlid) |
---|
325 | if (allocated(y%tautot_atlid)) deallocate(y%tautot_atlid) |
---|
326 | if (allocated(y%fracPrecipIce)) deallocate(y%fracPrecipIce) |
---|
327 | |
---|
328 | end subroutine destroy_cospIN |
---|
329 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
330 | ! SUBROUTINE destroy_cospstateIN |
---|
331 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
332 | subroutine destroy_cospstateIN(y) |
---|
333 | type(cosp_column_inputs),intent(inout) :: y |
---|
334 | |
---|
335 | if (allocated(y%sunlit)) deallocate(y%sunlit) |
---|
336 | if (allocated(y%skt)) deallocate(y%skt) |
---|
337 | if (allocated(y%land)) deallocate(y%land) |
---|
338 | if (allocated(y%at)) deallocate(y%at) |
---|
339 | if (allocated(y%pfull)) deallocate(y%pfull) |
---|
340 | if (allocated(y%phalf)) deallocate(y%phalf) |
---|
341 | if (allocated(y%qv)) deallocate(y%qv) |
---|
342 | if (allocated(y%o3)) deallocate(y%o3) |
---|
343 | if (allocated(y%hgt_matrix)) deallocate(y%hgt_matrix) |
---|
344 | if (allocated(y%u_sfc)) deallocate(y%u_sfc) |
---|
345 | if (allocated(y%v_sfc)) deallocate(y%v_sfc) |
---|
346 | if (allocated(y%lat)) deallocate(y%lat) |
---|
347 | if (allocated(y%lon)) deallocate(y%lon) |
---|
348 | if (allocated(y%emis_sfc)) deallocate(y%emis_sfc) |
---|
349 | if (allocated(y%cloudIce)) deallocate(y%cloudIce) |
---|
350 | if (allocated(y%cloudLiq)) deallocate(y%cloudLiq) |
---|
351 | if (allocated(y%seaice)) deallocate(y%seaice) |
---|
352 | if (allocated(y%fl_rain)) deallocate(y%fl_rain) |
---|
353 | if (allocated(y%fl_snow)) deallocate(y%fl_snow) |
---|
354 | if (allocated(y%tca)) deallocate(y%tca) |
---|
355 | if (allocated(y%hgt_matrix_half)) deallocate(y%hgt_matrix_half) |
---|
356 | if (allocated(y%surfelev)) deallocate(y%surfelev) |
---|
357 | |
---|
358 | end subroutine destroy_cospstateIN |
---|
359 | |
---|
360 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
361 | ! SUBROUTINE destroy_cosp_outputs |
---|
362 | !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
363 | subroutine destroy_cosp_outputs(y) |
---|
364 | type(cosp_outputs),intent(inout) :: y |
---|
365 | |
---|
366 | ! Deallocate and nullify |
---|
367 | if (associated(y%calipso_beta_mol)) then |
---|
368 | deallocate(y%calipso_beta_mol) |
---|
369 | nullify(y%calipso_beta_mol) |
---|
370 | endif |
---|
371 | if (associated(y%calipso_temp_tot)) then |
---|
372 | deallocate(y%calipso_temp_tot) |
---|
373 | nullify(y%calipso_temp_tot) |
---|
374 | endif |
---|
375 | if (associated(y%calipso_betaperp_tot)) then |
---|
376 | deallocate(y%calipso_betaperp_tot) |
---|
377 | nullify(y%calipso_betaperp_tot) |
---|
378 | endif |
---|
379 | if (associated(y%calipso_beta_tot)) then |
---|
380 | deallocate(y%calipso_beta_tot) |
---|
381 | nullify(y%calipso_beta_tot) |
---|
382 | endif |
---|
383 | if (associated(y%calipso_tau_tot)) then |
---|
384 | deallocate(y%calipso_tau_tot) |
---|
385 | nullify(y%calipso_tau_tot) |
---|
386 | endif |
---|
387 | if (associated(y%calipso_lidarcldphase)) then |
---|
388 | deallocate(y%calipso_lidarcldphase) |
---|
389 | nullify(y%calipso_lidarcldphase) |
---|
390 | endif |
---|
391 | if (associated(y%calipso_lidarcldtype)) then |
---|
392 | deallocate(y%calipso_lidarcldtype) |
---|
393 | nullify(y%calipso_lidarcldtype) |
---|
394 | endif |
---|
395 | if (associated(y%calipso_cldlayerphase)) then |
---|
396 | deallocate(y%calipso_cldlayerphase) |
---|
397 | nullify(y%calipso_cldlayerphase) |
---|
398 | endif |
---|
399 | if (associated(y%calipso_lidarcldtmp)) then |
---|
400 | deallocate(y%calipso_lidarcldtmp) |
---|
401 | nullify(y%calipso_lidarcldtmp) |
---|
402 | endif |
---|
403 | if (associated(y%calipso_cldlayer)) then |
---|
404 | deallocate(y%calipso_cldlayer) |
---|
405 | nullify(y%calipso_cldlayer) |
---|
406 | endif |
---|
407 | if (associated(y%calipso_cldtype)) then |
---|
408 | deallocate(y%calipso_cldtype) |
---|
409 | nullify(y%calipso_cldtype) |
---|
410 | endif |
---|
411 | if (associated(y%calipso_cldtypetemp)) then |
---|
412 | deallocate(y%calipso_cldtypetemp) |
---|
413 | nullify(y%calipso_cldtypetemp) |
---|
414 | endif |
---|
415 | if (associated(y%calipso_cldtypemeanz)) then |
---|
416 | deallocate(y%calipso_cldtypemeanz) |
---|
417 | nullify(y%calipso_cldtypemeanz) |
---|
418 | endif |
---|
419 | if (associated(y%calipso_cldtypemeanzse)) then |
---|
420 | deallocate(y%calipso_cldtypemeanzse) |
---|
421 | nullify(y%calipso_cldtypemeanzse) |
---|
422 | endif |
---|
423 | if (associated(y%calipso_cldthinemis)) then |
---|
424 | deallocate(y%calipso_cldthinemis) |
---|
425 | nullify(y%calipso_cldthinemis) |
---|
426 | endif |
---|
427 | if (associated(y%calipso_lidarcld)) then |
---|
428 | deallocate(y%calipso_lidarcld) |
---|
429 | nullify(y%calipso_lidarcld) |
---|
430 | endif |
---|
431 | if (associated(y%calipso_srbval)) then |
---|
432 | deallocate(y%calipso_srbval) |
---|
433 | nullify(y%calipso_srbval) |
---|
434 | endif |
---|
435 | if (associated(y%calipso_cfad_sr)) then |
---|
436 | deallocate(y%calipso_cfad_sr) |
---|
437 | nullify(y%calipso_cfad_sr) |
---|
438 | endif |
---|
439 | if (associated(y%grLidar532_beta_mol)) then |
---|
440 | deallocate(y%grLidar532_beta_mol) |
---|
441 | nullify(y%grLidar532_beta_mol) |
---|
442 | endif |
---|
443 | if (associated(y%grLidar532_beta_tot)) then |
---|
444 | deallocate(y%grLidar532_beta_tot) |
---|
445 | nullify(y%grLidar532_beta_tot) |
---|
446 | endif |
---|
447 | if (associated(y%grLidar532_cldlayer)) then |
---|
448 | deallocate(y%grLidar532_cldlayer) |
---|
449 | nullify(y%grLidar532_cldlayer) |
---|
450 | endif |
---|
451 | if (associated(y%grLidar532_lidarcld)) then |
---|
452 | deallocate(y%grLidar532_lidarcld) |
---|
453 | nullify(y%grLidar532_lidarcld) |
---|
454 | endif |
---|
455 | if (associated(y%grLidar532_cfad_sr)) then |
---|
456 | deallocate(y%grLidar532_cfad_sr) |
---|
457 | nullify(y%grLidar532_cfad_sr) |
---|
458 | endif |
---|
459 | if (associated(y%grLidar532_srbval)) then |
---|
460 | deallocate(y%grLidar532_srbval) |
---|
461 | nullify(y%grLidar532_srbval) |
---|
462 | endif |
---|
463 | if (associated(y%atlid_beta_mol)) then |
---|
464 | deallocate(y%atlid_beta_mol) |
---|
465 | nullify(y%atlid_beta_mol) |
---|
466 | endif |
---|
467 | if (associated(y%atlid_beta_tot)) then |
---|
468 | deallocate(y%atlid_beta_tot) |
---|
469 | nullify(y%atlid_beta_tot) |
---|
470 | endif |
---|
471 | if (associated(y%atlid_cldlayer)) then |
---|
472 | deallocate(y%atlid_cldlayer) |
---|
473 | nullify(y%atlid_cldlayer) |
---|
474 | endif |
---|
475 | if (associated(y%atlid_lidarcld)) then |
---|
476 | deallocate(y%atlid_lidarcld) |
---|
477 | nullify(y%atlid_lidarcld) |
---|
478 | endif |
---|
479 | if (associated(y%atlid_cfad_sr)) then |
---|
480 | deallocate(y%atlid_cfad_sr) |
---|
481 | nullify(y%atlid_cfad_sr) |
---|
482 | endif |
---|
483 | if (associated(y%atlid_srbval)) then |
---|
484 | deallocate(y%atlid_srbval) |
---|
485 | nullify(y%atlid_srbval) |
---|
486 | endif |
---|
487 | if (associated(y%parasolPix_refl)) then |
---|
488 | deallocate(y%parasolPix_refl) |
---|
489 | nullify(y%parasolPix_refl) |
---|
490 | endif |
---|
491 | if (associated(y%parasolGrid_refl)) then |
---|
492 | deallocate(y%parasolGrid_refl) |
---|
493 | nullify(y%parasolGrid_refl) |
---|
494 | endif |
---|
495 | if (associated(y%cloudsat_Ze_tot)) then |
---|
496 | deallocate(y%cloudsat_Ze_tot) |
---|
497 | nullify(y%cloudsat_Ze_tot) |
---|
498 | endif |
---|
499 | if (associated(y%cloudsat_cfad_ze)) then |
---|
500 | deallocate(y%cloudsat_cfad_ze) |
---|
501 | nullify(y%cloudsat_cfad_ze) |
---|
502 | endif |
---|
503 | if (associated(y%cloudsat_precip_cover)) then |
---|
504 | deallocate(y%cloudsat_precip_cover) |
---|
505 | nullify(y%cloudsat_precip_cover) |
---|
506 | endif |
---|
507 | if (associated(y%cloudsat_pia)) then |
---|
508 | deallocate(y%cloudsat_pia) |
---|
509 | nullify(y%cloudsat_pia) |
---|
510 | endif |
---|
511 | if (associated(y%cloudsat_tcc)) then |
---|
512 | deallocate(y%cloudsat_tcc) |
---|
513 | nullify(y%cloudsat_tcc) |
---|
514 | endif |
---|
515 | if (associated(y%cloudsat_tcc2)) then |
---|
516 | deallocate(y%cloudsat_tcc2) |
---|
517 | nullify(y%cloudsat_tcc2) |
---|
518 | endif |
---|
519 | if (associated(y%radar_lidar_tcc)) then |
---|
520 | deallocate(y%radar_lidar_tcc) |
---|
521 | nullify(y%radar_lidar_tcc) |
---|
522 | endif |
---|
523 | if (associated(y%cloudsat_tcc)) then |
---|
524 | deallocate(y%cloudsat_tcc) |
---|
525 | nullify(y%cloudsat_tcc) |
---|
526 | endif |
---|
527 | if (associated(y%cloudsat_tcc2)) then |
---|
528 | deallocate(y%cloudsat_tcc2) |
---|
529 | nullify(y%cloudsat_tcc2) |
---|
530 | endif |
---|
531 | if (associated(y%lidar_only_freq_cloud)) then |
---|
532 | deallocate(y%lidar_only_freq_cloud) |
---|
533 | nullify(y%lidar_only_freq_cloud) |
---|
534 | endif |
---|
535 | if (associated(y%isccp_totalcldarea)) then |
---|
536 | deallocate(y%isccp_totalcldarea) |
---|
537 | nullify(y%isccp_totalcldarea) |
---|
538 | endif |
---|
539 | if (associated(y%isccp_meantb)) then |
---|
540 | deallocate(y%isccp_meantb) |
---|
541 | nullify(y%isccp_meantb) |
---|
542 | endif |
---|
543 | if (associated(y%isccp_meantbclr)) then |
---|
544 | deallocate(y%isccp_meantbclr) |
---|
545 | nullify(y%isccp_meantbclr) |
---|
546 | endif |
---|
547 | if (associated(y%isccp_meanptop)) then |
---|
548 | deallocate(y%isccp_meanptop) |
---|
549 | nullify(y%isccp_meanptop) |
---|
550 | endif |
---|
551 | if (associated(y%isccp_meantaucld)) then |
---|
552 | deallocate(y%isccp_meantaucld) |
---|
553 | nullify(y%isccp_meantaucld) |
---|
554 | endif |
---|
555 | if (associated(y%isccp_meanalbedocld)) then |
---|
556 | deallocate(y%isccp_meanalbedocld) |
---|
557 | nullify(y%isccp_meanalbedocld) |
---|
558 | endif |
---|
559 | if (associated(y%isccp_boxtau)) then |
---|
560 | deallocate(y%isccp_boxtau) |
---|
561 | nullify(y%isccp_boxtau) |
---|
562 | endif |
---|
563 | if (associated(y%isccp_boxptop)) then |
---|
564 | deallocate(y%isccp_boxptop) |
---|
565 | nullify(y%isccp_boxptop) |
---|
566 | endif |
---|
567 | if (associated(y%isccp_fq)) then |
---|
568 | deallocate(y%isccp_fq) |
---|
569 | nullify(y%isccp_fq) |
---|
570 | endif |
---|
571 | if (associated(y%misr_fq)) then |
---|
572 | deallocate(y%misr_fq) |
---|
573 | nullify(y%misr_fq) |
---|
574 | endif |
---|
575 | if (associated(y%misr_dist_model_layertops)) then |
---|
576 | deallocate(y%misr_dist_model_layertops) |
---|
577 | nullify(y%misr_dist_model_layertops) |
---|
578 | endif |
---|
579 | if (associated(y%misr_meanztop)) then |
---|
580 | deallocate(y%misr_meanztop) |
---|
581 | nullify(y%misr_meanztop) |
---|
582 | endif |
---|
583 | if (associated(y%misr_cldarea)) then |
---|
584 | deallocate(y%misr_cldarea) |
---|
585 | nullify(y%misr_cldarea) |
---|
586 | endif |
---|
587 | if (associated(y%rttov_tbs)) then |
---|
588 | deallocate(y%rttov_tbs) |
---|
589 | nullify(y%rttov_tbs) |
---|
590 | endif |
---|
591 | if (associated(y%modis_Cloud_Fraction_Total_Mean)) then |
---|
592 | deallocate(y%modis_Cloud_Fraction_Total_Mean) |
---|
593 | nullify(y%modis_Cloud_Fraction_Total_Mean) |
---|
594 | endif |
---|
595 | if (associated(y%modis_Cloud_Fraction_Ice_Mean)) then |
---|
596 | deallocate(y%modis_Cloud_Fraction_Ice_Mean) |
---|
597 | nullify(y%modis_Cloud_Fraction_Ice_Mean) |
---|
598 | endif |
---|
599 | if (associated(y%modis_Cloud_Fraction_Water_Mean)) then |
---|
600 | deallocate(y%modis_Cloud_Fraction_Water_Mean) |
---|
601 | nullify(y%modis_Cloud_Fraction_Water_Mean) |
---|
602 | endif |
---|
603 | if (associated(y%modis_Cloud_Fraction_High_Mean)) then |
---|
604 | deallocate(y%modis_Cloud_Fraction_High_Mean) |
---|
605 | nullify(y%modis_Cloud_Fraction_High_Mean) |
---|
606 | endif |
---|
607 | if (associated(y%modis_Cloud_Fraction_Mid_Mean)) then |
---|
608 | deallocate(y%modis_Cloud_Fraction_Mid_Mean) |
---|
609 | nullify(y%modis_Cloud_Fraction_Mid_Mean) |
---|
610 | endif |
---|
611 | if (associated(y%modis_Cloud_Fraction_Low_Mean)) then |
---|
612 | deallocate(y%modis_Cloud_Fraction_Low_Mean) |
---|
613 | nullify(y%modis_Cloud_Fraction_Low_Mean) |
---|
614 | endif |
---|
615 | if (associated(y%modis_Optical_Thickness_Total_Mean)) then |
---|
616 | deallocate(y%modis_Optical_Thickness_Total_Mean) |
---|
617 | nullify(y%modis_Optical_Thickness_Total_Mean) |
---|
618 | endif |
---|
619 | if (associated(y%modis_Optical_Thickness_Water_Mean)) then |
---|
620 | deallocate(y%modis_Optical_Thickness_Water_Mean) |
---|
621 | nullify(y%modis_Optical_Thickness_Water_Mean) |
---|
622 | endif |
---|
623 | if (associated(y%modis_Optical_Thickness_Ice_Mean)) then |
---|
624 | deallocate(y%modis_Optical_Thickness_Ice_Mean) |
---|
625 | nullify(y%modis_Optical_Thickness_Ice_Mean) |
---|
626 | endif |
---|
627 | if (associated(y%modis_Optical_Thickness_Total_LogMean)) then |
---|
628 | deallocate(y%modis_Optical_Thickness_Total_LogMean) |
---|
629 | nullify(y%modis_Optical_Thickness_Total_LogMean) |
---|
630 | endif |
---|
631 | if (associated(y%modis_Optical_Thickness_Water_LogMean)) then |
---|
632 | deallocate(y%modis_Optical_Thickness_Water_LogMean) |
---|
633 | nullify(y%modis_Optical_Thickness_Water_LogMean) |
---|
634 | endif |
---|
635 | if (associated(y%modis_Optical_Thickness_Ice_LogMean)) then |
---|
636 | deallocate(y%modis_Optical_Thickness_Ice_LogMean) |
---|
637 | nullify(y%modis_Optical_Thickness_Ice_LogMean) |
---|
638 | endif |
---|
639 | if (associated(y%modis_Cloud_Particle_Size_Water_Mean)) then |
---|
640 | deallocate(y%modis_Cloud_Particle_Size_Water_Mean) |
---|
641 | nullify(y%modis_Cloud_Particle_Size_Water_Mean) |
---|
642 | endif |
---|
643 | if (associated(y%modis_Cloud_Particle_Size_Ice_Mean)) then |
---|
644 | deallocate(y%modis_Cloud_Particle_Size_Ice_Mean) |
---|
645 | nullify(y%modis_Cloud_Particle_Size_Ice_Mean) |
---|
646 | endif |
---|
647 | if (associated(y%modis_Cloud_Top_Pressure_Total_Mean)) then |
---|
648 | deallocate(y%modis_Cloud_Top_Pressure_Total_Mean) |
---|
649 | nullify(y%modis_Cloud_Top_Pressure_Total_Mean) |
---|
650 | endif |
---|
651 | if (associated(y%modis_Liquid_Water_Path_Mean)) then |
---|
652 | deallocate(y%modis_Liquid_Water_Path_Mean) |
---|
653 | nullify(y%modis_Liquid_Water_Path_Mean) |
---|
654 | endif |
---|
655 | if (associated(y%modis_Ice_Water_Path_Mean)) then |
---|
656 | deallocate(y%modis_Ice_Water_Path_Mean) |
---|
657 | nullify(y%modis_Ice_Water_Path_Mean) |
---|
658 | endif |
---|
659 | if (associated(y%modis_Optical_Thickness_vs_Cloud_Top_Pressure)) then |
---|
660 | deallocate(y%modis_Optical_Thickness_vs_Cloud_Top_Pressure) |
---|
661 | nullify(y%modis_Optical_Thickness_vs_Cloud_Top_Pressure) |
---|
662 | endif |
---|
663 | if (associated(y%modis_Optical_thickness_vs_ReffLIQ)) then |
---|
664 | deallocate(y%modis_Optical_thickness_vs_ReffLIQ) |
---|
665 | nullify(y%modis_Optical_thickness_vs_ReffLIQ) |
---|
666 | endif |
---|
667 | if (associated(y%modis_Optical_thickness_vs_ReffICE)) then |
---|
668 | deallocate(y%modis_Optical_thickness_vs_ReffICE) |
---|
669 | nullify(y%modis_Optical_thickness_vs_ReffICE) |
---|
670 | endif |
---|
671 | |
---|
672 | end subroutine destroy_cosp_outputs |
---|
673 | |
---|
674 | END MODULE LMDZ_COSP_CONSTRUCT_DESTROY_MOD |
---|
675 | |
---|