Line data Source code
1 : !------------------------------------------------------------------------------
2 : ! Harmonized Emissions Component (HEMCO) !
3 : !------------------------------------------------------------------------------
4 : !BOP
5 : !
6 : ! !MODULE: hcox_seaflux_mod.F90
7 : !
8 : ! !DESCRIPTION: Module HCOX\_SeaFlux\_Mod contains routines to calculate
9 : ! the oceanic emissions of a number of defined species.
10 : ! The oceanic flux is parameterized according to Liss and Slater, 1974:
11 : ! F = Kg * ( Cair - H Cwater )
12 : ! where F is the net flux, Kg is the exchange velocity, Cair and Cwater
13 : ! are the air and aqueous concentrations, respectively, and H is the
14 : ! dimensionless air over water Henry constant.
15 : !\\
16 : !\\
17 : ! This module calculates the source and sink terms separately. The source
18 : ! is given as flux, the sink as deposition rate:
19 : ! source = Kg * H * Cwater [kg m-2 s-1]
20 : ! sink = Kg / DEPHEIGHT [s-1]
21 : !
22 : ! The deposition rate is obtained by dividing the exchange velocity Kg
23 : ! by the deposition height DEPHEIGHT, e.g. the height over which
24 : ! deposition occurs. This can be either the first grid box only, or the
25 : ! entire planetary boundary layer. The HEMCO option 'PBL\_DRYDEP' determines
26 : ! which option is being used.
27 : !\\
28 : !\\
29 : ! Kg is calculated following Johnson, 2010, which is largely based on
30 : ! the work of Nightingale et al., 2000a/b.
31 : ! The salinity and seawater pH are currently set to constant global values
32 : ! of 35 ppt and 8.0, respectively.
33 : ! Since Kg is only little sensitive to these variables, this should not
34 : ! introduce a notable error.
35 : !\\
36 : !\\
37 : ! This is a HEMCO extension module that uses many of the HEMCO core
38 : ! utilities.
39 : !\\
40 : !\\
41 : ! Air-sea exchange is calculated for all species defined during
42 : ! extension initialization. For each species, the following parameter
43 : ! must be specified: species name, model species ID (i.e. ID of this
44 : ! species in the external model), parameterization type of Schmidt
45 : ! number in water, liquid molar volume of species, and the name of the
46 : ! field containing species sea-water concentrations. See initialization
47 : ! routine for more details.
48 : ! To add new species to this module, the abovementioned arrays have to
49 : ! be extended accordingly.
50 : !\\
51 : !\\
52 : ! References:
53 : ! \begin{itemize}
54 : ! \item Johnson, M.: A numerical scheme to calculate temperature and salinity
55 : ! dependent air-water transfer velocities for any gas, Ocean Science, 6,
56 : ! 2010.
57 : ! \item Liss and Slater: Flux of gases across the air-sea interface, Nature,
58 : ! 247, 1974.
59 : ! \item Nightingale et al.: In situ evaluation of air-sea gas exchange
60 : ! parameterizations using novel conservative and volatile tracers,
61 : ! Global Biogeochemical Cycles, 14, 2000a.
62 : ! \item Nightingale et al.: Measurements of air-sea gas transfer during an
63 : ! open ocean algal bloom, Geophys. Res. Lett., 27, 2000b.
64 : ! \item Saltzman et al.: Experimental determination of the diffusion
65 : ! coefficient of dimethylsulfide in water, J. Geophys. Res., 98, 1993.
66 : ! \end{itemize}
67 : !
68 : ! !INTERFACE:
69 : !
70 : MODULE HCOX_SeaFlux_Mod
71 : !
72 : ! !USES:
73 : !
74 : USE HCO_Error_MOD
75 : USE HCO_Diagn_MOD
76 : USE HCO_State_MOD, ONLY : HCO_State
77 : USE HCOX_State_MOD, ONLY : Ext_State
78 :
79 : IMPLICIT NONE
80 : PRIVATE
81 : !
82 : ! !PUBLIC MEMBER FUNCTIONS:
83 : !
84 : PUBLIC :: HCOX_SeaFlux_Init
85 : PUBLIC :: HCOX_SeaFlux_Run
86 : PUBLIC :: HCOX_SeaFlux_Final
87 : !
88 : ! !PRIVATE MEMBER FUNCTIONS:
89 : !
90 : PRIVATE :: Calc_SeaFlux
91 : !
92 : ! !REVISION HISTORY:
93 : ! 16 Apr 2013 - C. Keller - Initial version
94 : ! See https://github.com/geoschem/hemco for complete history
95 : !EOP
96 : !------------------------------------------------------------------------------
97 : !
98 : ! !PRIVATE TYPES:
99 : !
100 : ! Ocean species
101 : TYPE :: OcSpec
102 : INTEGER :: HcoID ! HEMCO species ID
103 : CHARACTER(LEN=31) :: OcSpcName ! oc. species name
104 : CHARACTER(LEN=31) :: OcDataName ! seawater conc. field name
105 : REAL*8 :: LiqVol ! liq. molecular volume
106 : INTEGER :: SCWPAR ! Schmidt # parameterization type
107 : END TYPE OcSpec
108 :
109 : TYPE :: MyInst
110 : ! Tracer IDs
111 : INTEGER :: Instance
112 : ! Variables carrying information about ocean species
113 : INTEGER :: ExtNr
114 : INTEGER :: nOcSpc ! # of ocean species
115 : TYPE(OcSpec), POINTER :: OcSpecs(:)
116 : TYPE(MyInst), POINTER :: NextInst => NULL()
117 : END TYPE MyInst
118 :
119 : ! Pointer to instances
120 : TYPE(MyInst), POINTER :: AllInst => NULL()
121 :
122 : CONTAINS
123 : !EOC
124 : !------------------------------------------------------------------------------
125 : ! Harmonized Emissions Component (HEMCO) !
126 : !------------------------------------------------------------------------------
127 : !BOP
128 : !
129 : ! !IROUTINE: HCOX_SeaFlux_Run
130 : !
131 : ! !DESCRIPTION: Subroutine HcoX\_SeaFlux\_Run is the run routine to
132 : ! calculate oceanic emissions for the current time step.
133 : !\\
134 : !\\
135 : ! !INTERFACE:
136 : !
137 0 : SUBROUTINE HCOX_SeaFlux_Run( ExtState, HcoState, RC )
138 : !
139 : ! !USES:
140 : !
141 : USE HCO_FLUXARR_MOD, ONLY : HCO_EmisAdd
142 : USE HCO_FLUXARR_MOD, ONLY : HCO_DepvAdd
143 : USE HCO_CALC_MOD, ONLY : HCO_EvalFld
144 : ! USE HCO_EMISLIST_MOD, ONLY : HCO_GetPtr
145 : !
146 : ! !INPUT PARAMETERS:
147 : !
148 : TYPE(HCO_State), POINTER :: HcoState ! Output obj
149 : TYPE(Ext_State), POINTER :: ExtState ! Module options
150 : !
151 : ! !INPUT/OUTPUT PARAMETERS:
152 : !
153 : INTEGER, INTENT(INOUT) :: RC ! Success or failure?
154 : !
155 : ! !REVISION HISTORY:
156 : ! 16 Apr 2013 - C. Keller - Initial version
157 : ! See https://github.com/geoschem/hemco for complete history
158 : !EOP
159 : !------------------------------------------------------------------------------
160 : !BOC
161 : !
162 : ! !LOCAL VARIABLES:
163 : !
164 : ! Scalars
165 : TYPE(MyInst), POINTER :: Inst
166 : INTEGER :: OcID, HcoID
167 0 : REAL(hp), TARGET :: SOURCE(HcoState%NX,HcoState%NY)
168 0 : REAL(hp), TARGET :: SINK (HcoState%NX,HcoState%NY)
169 0 : REAL(hp), TARGET :: SeaConc(HcoState%NX,HcoState%NY)
170 : CHARACTER(LEN=255) :: ContName
171 : CHARACTER(LEN=255) :: MSG, LOC
172 : LOGICAL :: VERBOSE
173 :
174 : ! Pointers
175 0 : REAL(hp), POINTER :: Arr2D(:,:)
176 :
177 : !=================================================================
178 : ! HCOX_SeaFlux_Run begins here!
179 : !=================================================================
180 0 : LOC = 'HCOX_SeaFlux_Run (HCOX_SEAFLUX_MOD.F90)'
181 :
182 : ! Enter
183 0 : CALL HCO_ENTER( HcoState%Config%Err, LOC, RC )
184 0 : IF ( RC /= HCO_SUCCESS ) THEN
185 0 : CALL HCO_ERROR( 'ERROR 0', RC, THISLOC=LOC )
186 0 : RETURN
187 : ENDIF
188 :
189 : ! Return if extension disabled
190 0 : IF ( ExtState%SeaFlux <= 0 ) RETURN
191 :
192 : ! Verbose?
193 0 : verbose = HCO_IsVerb(HcoState%Config%Err,1)
194 :
195 : ! Nullify
196 0 : Arr2D => NULL()
197 :
198 : ! Get instance
199 0 : Inst => NULL()
200 0 : CALL InstGet ( ExtState%SeaFlux, Inst, RC )
201 0 : IF ( RC /= HCO_SUCCESS ) THEN
202 0 : WRITE(MSG,*) 'Cannot find SeaFlux instance Nr. ', ExtState%SeaFlux
203 0 : CALL HCO_ERROR(MSG,RC)
204 0 : RETURN
205 : ENDIF
206 :
207 : ! ---------------------------------------------------------------
208 : ! Calculate emissions
209 : ! ---------------------------------------------------------------
210 :
211 : ! Loop over all model species
212 0 : DO OcID = 1, Inst%nOcSpc
213 :
214 : ! Get HEMCO species ID
215 0 : HcoID = Inst%OcSpecs(OcID)%HcoID
216 :
217 : ! Skip this species if it has no corresponding HEMCO and/or
218 : ! model species
219 0 : IF ( HcoID < 0 ) CYCLE
220 0 : IF ( HcoState%Spc(HcoID)%ModID < 0 ) CYCLE
221 :
222 0 : IF ( verbose ) THEN
223 : WRITE(MSG,'(A40,I5)') &
224 0 : 'Calculate air-sea flux for HEMCO species', HcoID
225 0 : CALL HCO_MSG(HcoState%Config%Err,MSG)
226 0 : WRITE(MSG,*) 'Module species name: ', &
227 0 : TRIM(Inst%OcSpecs(OcID)%OcSpcName)
228 0 : CALL HCO_MSG(HcoState%Config%Err,MSG)
229 : ENDIF
230 :
231 : ! Get seawater concentration of given compound (from HEMCO core).
232 0 : ContName = TRIM(Inst%OcSpecs(OcID)%OcDataName)
233 0 : CALL HCO_EvalFld ( HcoState, ContName, SeaConc, RC )
234 0 : IF ( RC /= HCO_SUCCESS ) THEN
235 0 : CALL HCO_ERROR( 'ERROR 1', RC, THISLOC=LOC )
236 0 : RETURN
237 : ENDIF
238 :
239 : ! Calculate oceanic source (kg/m2/s) as well as the deposition
240 : ! velocity (1/s).
241 : CALL Calc_SeaFlux ( HcoState, ExtState, Inst, &
242 : SOURCE, SINK, SeaConc, &
243 0 : OcID, HcoID, RC )
244 0 : IF ( RC /= HCO_SUCCESS ) THEN
245 0 : CALL HCO_ERROR( 'ERROR 2', RC, THISLOC=LOC )
246 0 : RETURN
247 : ENDIF
248 :
249 : ! Set flux in HEMCO object [kg/m2/s]
250 0 : CALL HCO_EmisAdd ( HcoState, SOURCE, HcoID, RC, ExtNr=Inst%ExtNr )
251 0 : IF ( RC /= HCO_SUCCESS ) THEN
252 0 : MSG = 'HCO_EmisAdd error: ' // TRIM(Inst%OcSpecs(OcID)%OcSpcName)
253 0 : CALL HCO_ERROR(MSG, RC )
254 0 : RETURN
255 : ENDIF
256 : IF ( RC /= HCO_SUCCESS ) THEN
257 : CALL HCO_ERROR( 'ERROR 3', RC, THISLOC=LOC )
258 : RETURN
259 : ENDIF
260 :
261 : ! Set deposition velocity in HEMCO object [1/s]
262 0 : CALL HCO_DepvAdd ( HcoState, SINK, HcoID, RC )
263 0 : IF ( RC /= HCO_SUCCESS ) THEN
264 0 : CALL HCO_ERROR( 'ERROR 4', RC, THISLOC=LOC )
265 0 : RETURN
266 : ENDIF
267 :
268 : ! Free pointers
269 : !SeaConc => NULL()
270 :
271 : ! Eventually add to dry deposition diagnostics
272 0 : ContName = 'DRYDEP_VEL_' // TRIM(HcoState%Spc(HcoID)%SpcName)
273 0 : Arr2D => SINK
274 : CALL Diagn_Update( HcoState, &
275 : cName = TRIM(ContName), &
276 : Array2D = Arr2D, &
277 : COL = -1, &
278 0 : RC = RC )
279 0 : Arr2D => NULL()
280 : ENDDO !SpcID
281 :
282 : ! Cleanup
283 0 : Inst => NULL()
284 :
285 : ! Leave w/ success
286 0 : CALL HCO_LEAVE( HcoState%Config%Err,RC )
287 :
288 0 : END SUBROUTINE HCOX_SeaFlux_Run
289 : !EOC
290 : !------------------------------------------------------------------------------
291 : ! Harmonized Emissions Component (HEMCO) !
292 : !------------------------------------------------------------------------------
293 : !BOP
294 : !
295 : ! !IROUTINE: Calc_SeaFlux
296 : !
297 : ! !DESCRIPTION: Subroutine CALC\_SEAFLUX calculates oceanic emissions
298 : ! of the specified tracer using the parameterization described in
299 : ! Johnson, 2010.
300 : !\\
301 : !\\
302 : ! The net emission flux is given by F = - Kg ( Cg - Caq*H ). Here, we
303 : ! calculate the source term ( Kg * H * Caq ) in units of kg/m2/s as
304 : ! well as the deposition velocity Kg in m/s.
305 : !\\
306 : !\\
307 : ! !INTERFACE:
308 : !
309 0 : SUBROUTINE Calc_SeaFlux( HcoState, ExtState, &
310 0 : Inst, SOURCE, SINK, &
311 0 : SeaConc, OcID, HcoID, RC )
312 : !
313 : ! !USES:
314 : !
315 : USE ieee_arithmetic, ONLY : ieee_is_finite
316 : USE Ocean_ToolBox_Mod, ONLY : CALC_KG
317 : USE Hco_Henry_Mod, ONLY : CALC_KH, CALC_HEFF
318 : USE HCO_CALC_MOD, ONLY : HCO_CheckDepv
319 : USE HCO_GeoTools_Mod, ONLY : HCO_LANDTYPE
320 : !
321 : ! !INPUT PARAMETERS:
322 : !
323 : INTEGER, INTENT(IN ) :: OcID ! ocean species ID
324 : INTEGER, INTENT(IN ) :: HcoID ! HEMCO species ID
325 : TYPE(HCO_State), POINTER :: HcoState ! Output obj
326 : TYPE(Ext_State), POINTER :: ExtState
327 : TYPE(MyInst), POINTER :: Inst
328 : !
329 : ! !OUTPUT PARAMETERS:
330 : !
331 : REAL(hp), INTENT( OUT) :: SOURCE(HcoState%NX,HcoState%NY )
332 : REAL(hp), INTENT( OUT) :: SINK (HcoState%NX,HcoState%NY )
333 : !
334 : ! !INPUT/OUTPUT PARAMETERS:
335 : !
336 : REAL(hp), INTENT(INOUT) :: SeaConc(HcoState%NX,HcoState%NY )
337 : INTEGER, INTENT(INOUT) :: RC ! Error stat
338 :
339 : !
340 : ! !REMARKS:
341 : ! For now, the salinity and pH of seawater are prescribed to 35ppt and 8.0,
342 : ! respectively. The oceanic flux is not expected to be sensitive to these
343 : ! parameters (which have only little variations anyway), but we may use
344 : ! climatologies for these parameter at some point nevertheless!
345 : !
346 : ! !REVISION HISTORY:
347 : ! 16 Apr 2013 - C. Keller - Initial version
348 : ! See https://github.com/geoschem/hemco for complete history
349 : !EOP
350 : !------------------------------------------------------------------------------
351 : !BOC
352 : !
353 : ! !LOCAL VARIABLES:
354 : !
355 : INTEGER :: I, J, L, N
356 : REAL*8 :: IJSRC
357 : INTEGER :: SCW
358 : REAL*8 :: P, V, VB, MW, KG
359 : REAL*8 :: K0, CR, PKA
360 : REAL*8 :: KH, HEFF
361 : REAL*8 :: TK, TC
362 : REAL(hp) :: DEP_HEIGHT
363 : INTEGER :: OLDWARN
364 : INTEGER :: PBL_MAX
365 : INTEGER, SAVE :: WARN = 0
366 :
367 : ! For now, hardcode salinity
368 : REAL(dp), PARAMETER :: S = 35.0_dp
369 :
370 : ! Set seawater PH to constant value of 8
371 : REAL(dp), PARAMETER :: PH = 8.0_dp
372 :
373 : ! Maximum allowed temperature (to avoid neg. Schmidt number)
374 : ! Set to 45 C (= 318.15 K)
375 : REAL(dp), PARAMETER :: TMAX = 318.15_dp
376 :
377 : ! Error handling
378 : CHARACTER(LEN=255) :: MSG, LOC
379 :
380 : !=================================================================
381 : ! CALC_SEAFLUX begins here!
382 : !=================================================================
383 0 : LOC = 'CALC_SEAFLUX (HCOX_SEAFLUX_MOD.F90)'
384 :
385 : ! Enter
386 0 : CALL HCO_ENTER( HcoState%Config%Err, LOC, RC )
387 0 : IF ( RC /= HCO_SUCCESS ) THEN
388 0 : CALL HCO_ERROR( 'ERROR 5', RC, THISLOC=LOC )
389 0 : RETURN
390 : ENDIF
391 :
392 : ! Init
393 0 : SOURCE = 0.0_hp
394 0 : SINK = 0.0_hp
395 :
396 : ! Extract Henry coefficients
397 0 : K0 = HcoState%Spc(HcoID)%HenryK0
398 0 : CR = HcoState%Spc(HcoID)%HenryCR
399 0 : PKA = HcoState%Spc(HcoID)%HenryPKA
400 :
401 : ! molecular weight [g/mol]
402 : ! Use real species molecular weight and not the emitted
403 : ! molecular weight. The molecular weight is only needed to
404 : ! calculate the air-side Schmidt number, which should be
405 : ! using the actual species MW.
406 0 : MW = HcoState%Spc(HcoID)%MW_g
407 :
408 : ! Liquid molar volume at boiling point [cm3/mol]
409 0 : VB = Inst%OcSpecs(OcID)%LiqVol
410 :
411 : ! Get parameterization type for Schmidt number in water
412 0 : SCW = Inst%OcSpecs(OcID)%SCWPAR
413 :
414 : ! Model surface layer
415 0 : L = 1
416 :
417 : ! Write out original warning status
418 0 : OLDWARN = WARN
419 :
420 : ! Loop over all grid boxes. Only emit into lowest layer
421 :
422 : !$OMP PARALLEL DO &
423 : !$OMP DEFAULT( SHARED ) &
424 : !$OMP PRIVATE( I, J, N, TK, TC ) &
425 : !$OMP PRIVATE( P, V, KH, RC, HEFF ) &
426 : !$OMP PRIVATE( KG, IJSRC, PBL_MAX, DEP_HEIGHT ) &
427 : !$OMP SCHEDULE( DYNAMIC )
428 :
429 0 : DO J = 1, HcoState%NY
430 0 : DO I = 1, HcoState%NX
431 :
432 : ! Make sure we have no negative seawater concentrations
433 0 : IF ( SeaConc(I,J) < 0.0_hp ) SeaConc(I,J) = 0.0_hp
434 :
435 : ! Do only over the ocean:
436 0 : IF ( HCO_LANDTYPE( ExtState%FRLAND%Arr%Val(I,J), &
437 0 : ExtState%FRLANDIC%Arr%Val(I,J), &
438 0 : ExtState%FROCEAN%Arr%Val(I,J), &
439 0 : ExtState%FRSEAICE%Arr%Val(I,J), &
440 0 : ExtState%FRLAKE%Arr%Val(I,J)) == 0 ) THEN
441 :
442 : !-----------------------------------------------------------
443 : ! Get grid box and species specific quantities
444 : !-----------------------------------------------------------
445 :
446 : ! skin surface temp in K
447 0 : TK = ExtState%TSKIN%Arr%Val(I,J)
448 :
449 : ! Error check: the Schmidt number may become negative for
450 : ! very high temperatures - hence cap temperature at specified
451 : ! limit
452 0 : IF ( TK > TMAX ) THEN
453 0 : WARN = 1
454 0 : TK = TMAX
455 : ENDIF
456 :
457 : ! Temperature in C
458 0 : TC = TK - 273.15d0
459 :
460 : ! Assume no air-sea exchange for temperatures below -10 deg C.
461 : ! This is rather arbitrary, but seawater should be frozen at
462 : ! that temperature anyways. Also, this ensures that the cal-
463 : ! culation of KG doesn't produce an overflow error, which occurs
464 : ! at temperatures of -10.7 to -10.9 deg C.
465 0 : IF ( TC < -10.0d0 ) CYCLE
466 :
467 : ! surface pressure [Pa]
468 0 : P = HcoState%Grid%PEDGE%Val(I,J,L)
469 :
470 : ! 10-m wind speed [m/s]
471 0 : V = ExtState%U10M%Arr%Val(I,J)**2 + &
472 0 : ExtState%V10M%Arr%Val(I,J)**2
473 0 : V = SQRT(V)
474 :
475 : ! Henry gas over liquid dimensionless constant and
476 : ! effective Henry constant [both unitless].
477 0 : CALL CALC_KH ( K0, CR, TK, KH, RC ) ! liquid over gas
478 : ! Exit here if error. Use error flags from henry_mod.F!
479 0 : IF ( RC /= 0 ) THEN
480 0 : RC = HCO_FAIL
481 0 : WRITE(MSG,*) 'Cannot calculate KH: ', K0, CR, TK
482 0 : EXIT
483 : ENDIF
484 0 : CALL CALC_HEFF ( PKA, PH, KH, HEFF, RC ) ! liquid over gas
485 : ! Exit here if error. Use error flags from henry_mod.F!
486 0 : IF ( RC /= 0 ) THEN
487 0 : RC = HCO_FAIL
488 0 : WRITE(MSG,*) 'Cannot calculate HEFF: ', PKA, PH, KH
489 0 : EXIT
490 : ENDIF
491 :
492 : ! Gas over liquid
493 0 : KH = 1d0 / KH
494 0 : HEFF = 1d0 / HEFF
495 :
496 : !-----------------------------------------------------------
497 : ! Calculate exchange velocity KG in [m s-1]
498 : !-----------------------------------------------------------
499 :
500 : ! Get exchange velocity KG (m/s) following Johnson, 2010.
501 : ! Kg is defined as 1 / (1/k_air + H/k_water). Note that Kg
502 : ! is denoted Ka in Johnson, 2010!
503 : ! Use effective Henry constant here to account for
504 : ! hydrolysis!
505 0 : CALL CALC_KG( TC, P, V, S, HEFF, VB, MW, SCW, KG, RC )
506 0 : IF ( RC /= 0 ) THEN
507 0 : RC = HCO_FAIL
508 0 : WRITE(MSG,*) 'Cannot calculate KG: ', TC, P, V, S, HEFF
509 0 : EXIT
510 : ENDIF
511 :
512 : !-----------------------------------------------------------
513 : ! Calculate flux from the ocean (kg m-2 s-1):
514 : !-----------------------------------------------------------
515 :
516 : ! Fwa = KG * Cwater * H (Liss and Slater, 1974)
517 : ! Oceanic concentration is im [kg m-3], H is
518 : ! dimensionless, and KG is [m s-1], so IJSRC is
519 : ! [kg m-2 s-1].
520 : ! OcArr already accounts for pH effects, so apply the
521 : ! 'regular' Henry constant H here.
522 0 : IJSRC = KG * KH * SeaConc(I,J)
523 :
524 : ! Pass to flux array
525 0 : SOURCE(I,J) = IJSRC
526 :
527 : !-----------------------------------------------------------
528 : ! Calculate deposition rate to the ocean (s-1):
529 : !-----------------------------------------------------------
530 :
531 : ! Determine deposition height based on HEMCO option regarding
532 : ! the deposition length scale.
533 0 : IF ( HcoState%Options%PBL_DRYDEP ) THEN
534 0 : DO N = HcoState%NZ, 1, -1
535 0 : IF ( ExtState%FRAC_OF_PBL%Arr%Val(I,J,N) > 0.0_hp ) THEN
536 : PBL_MAX = N
537 : EXIT
538 : ENDIF
539 : ENDDO
540 : ELSE
541 : PBL_MAX = 1
542 : ENDIF
543 0 : DEP_HEIGHT = SUM(HcoState%Grid%BXHEIGHT_M%Val(I,J,1:PBL_MAX))
544 :
545 : ! Now calculate deposition rate from velocity and deposition
546 : ! height: [s-1] = [m s-1] / [m].
547 0 : SINK(I,J) = KG / DEP_HEIGHT
548 :
549 : ! Check validity of value
550 : CALL HCO_CheckDepv( HcoState, SINK(I,J), RC )
551 :
552 : ENDIF !Over ocean
553 : ENDDO !I
554 : ENDDO !J
555 : !$OMP END PARALLEL DO
556 :
557 :
558 : ! Check exit status
559 0 : IF ( RC /= HCO_SUCCESS ) THEN
560 0 : CALL HCO_ERROR(MSG, RC )
561 0 : RETURN
562 : ENDIF
563 :
564 : ! Warning?
565 0 : IF ( WARN /= OLDWARN ) THEN
566 0 : WRITE(MSG,*) 'Temperature limited to ', TMAX, 'K'
567 0 : CALL HCO_WARNING(HcoState%Config%Err, MSG, RC )
568 : ENDIF
569 :
570 : ! Leave w/ success
571 0 : CALL HCO_LEAVE( HcoState%Config%Err,RC )
572 :
573 0 : END SUBROUTINE Calc_SeaFlux
574 : !EOC
575 : !------------------------------------------------------------------------------
576 : ! Harmonized Emissions Component (HEMCO) !
577 : !------------------------------------------------------------------------------
578 : !BOP
579 : !
580 : ! !IROUTINE: HCOX_SeaFlux_Init
581 : !
582 : ! !DESCRIPTION: Subroutine HCOX\_SeaFlux\_Init initializes all module
583 : ! variables, including all species - specific parameter such as
584 : ! the liquid molar volume (Vb), the parameterization type for the
585 : ! Schmidt number in water (SCWPAR) and the name of the field containing
586 : ! oceanic concentrations.
587 : !\\
588 : !\\
589 : ! LiqVol is the liquid molar volume [cm3/mol]. If not stated otherwise,
590 : ! it is calculated using the Schroeder additive method as described in
591 : ! Johnson, 2010. Note that experimental values for LiqVol should be used
592 : ! if available!
593 : !\\
594 : !\\
595 : ! Table 3 of Johnson, 2010: Schroeder additive method for calculating
596 : ! Vb. For all atoms/structural items a molecule contains, the sum of the
597 : ! incre- ments will give the molar volume. e.g. CH2=CH2 contains 2 car-
598 : ! bon atoms, 4 hydrogen atoms and 1 double bond so the Schroeder
599 : ! Vb is 2x7 + 4x7 + 7 = 49cm3mol-1. * applies to all kinds of cyclic features
600 : ! and is applied only once to ring-containing compounds irrespective
601 : ! of the number of rings present.
602 : !
603 : ! \begin{itemize}
604 : ! \item Atom/feature Increment/cm3mole-1
605 : ! \item Carbon 7.0
606 : ! \item Hydrogen 7.0
607 : ! \item Oxygen 7.0
608 : ! \item Nitrogen 7.0
609 : ! \item Bromine 31.5
610 : ! \item Chlorine 24.5
611 : ! \item Fluorine 10.5
612 : ! \item Iodine 38.5
613 : ! \item Sulfur 21.0
614 : ! \item Ring* -7.0
615 : ! \item Double bond 7.0
616 : ! \item Triple bond 14.0
617 : ! \end{itemize}
618 : !
619 : ! SCWPAR denotes which parameterization will be used to calculate the
620 : ! Schmidt number in water (in ocean\_toolbox\_mod). The following
621 : ! parameterizations are currently supported:
622 : !
623 : ! \begin{enumerate}
624 : ! \item Parameterization as in Johnson, 2010 (default).
625 : ! \item Parameterization for DMS according to Saltzman et al., 1993.
626 : ! \item Parameterization for Acetone as in former acetone\_mod.F in GC.
627 : ! \item Parameterization for Acetaldehyde as in ald2\_mod.F from D. Millet
628 : ! \item Parameterization for MENO3, ETNO3 as in Fisher et al., 2018
629 : ! \end{enumerate}
630 :
631 : ! The oceanic surface concentrations of all species are obtained from
632 : ! external fields. These field names are specified in array OcDataName.
633 : ! For now, we obtain these concentrations from netCDF-files through the
634 : ! HEMCO core module, i.e. for each species there need to be a
635 : ! corresponding seawater concentration data file specified in the HEMCO
636 : ! configuration file. Once we use a coupled (ESMF) system, these names
637 : ! may be used to refer to the names of the concentration fields imported
638 : ! from the ocean model component.
639 : !\\
640 : !\\
641 : ! !INTERFACE:
642 : !
643 0 : SUBROUTINE HCOX_SeaFlux_Init( HcoState, ExtName, ExtState, RC )
644 : !
645 : ! !USES:
646 : !
647 0 : USE HCO_ExtList_Mod, ONLY : GetExtNr
648 : USE HCO_STATE_MOD, ONLY : HCO_GetExtHcoID
649 : !
650 : ! !INPUT PARAMETERS:
651 : !
652 : TYPE(HCO_State), POINTER :: HcoState ! Hemco State obj.
653 : CHARACTER(LEN=*), INTENT(IN ) :: ExtName ! Extension name
654 : TYPE(Ext_State), POINTER :: ExtState ! Ext. obj.
655 : !
656 : ! !INPUT/OUTPUT PARAMETERS:
657 : !
658 : INTEGER, INTENT(INOUT) :: RC ! Return status
659 : !
660 : ! !REVISION HISTORY:
661 : ! 16 Apr 2013 - C. Keller - Initial version
662 : ! See https://github.com/geoschem/hemco for complete history
663 : !EOP
664 : !------------------------------------------------------------------------------
665 : !BOC
666 : !
667 : ! !LOCAL VARIABLES
668 : !
669 : ! Scalars
670 : TYPE(MyInst), POINTER :: Inst
671 : INTEGER :: ExtNr, I, J, nSpc
672 : CHARACTER(LEN=255) :: NAME_OC, MSG, ERR, LOC
673 :
674 : ! Arrays
675 0 : INTEGER, ALLOCATABLE :: HcoIDs(:)
676 0 : CHARACTER(LEN=31), ALLOCATABLE :: SpcNames(:)
677 :
678 : !=================================================================
679 : ! HCOX_SeaFlux_Init begins here!
680 : !=================================================================
681 0 : LOC = 'HCOX_SeaFlux_Init (HCOX_SEAFLUX_MOD.F90)'
682 :
683 : ! Extension Nr.
684 0 : ExtNr = GetExtNr( HcoState%Config%ExtList, TRIM(ExtName) )
685 0 : IF ( ExtNr <= 0 ) RETURN
686 :
687 : ! Enter
688 0 : CALL HCO_ENTER( HcoState%Config%Err, LOC, RC )
689 0 : IF ( RC /= HCO_SUCCESS ) THEN
690 0 : CALL HCO_ERROR( 'ERROR 6', RC, THISLOC=LOC )
691 0 : RETURN
692 : ENDIF
693 0 : ERR = 'nOcSpc too low!'
694 :
695 : ! Create instance for this simulation
696 0 : CALL InstCreate ( ExtNr, ExtState%SeaFlux, Inst, RC )
697 0 : IF ( RC /= HCO_SUCCESS ) THEN
698 0 : CALL HCO_ERROR ( 'Cannot create SeaFlux instance', RC )
699 0 : RETURN
700 : ENDIF
701 :
702 : ! Verbose mode
703 0 : IF ( HcoState%amIRoot ) THEN
704 0 : MSG = 'Use air-sea flux emissions (extension module)'
705 0 : CALL HCO_MSG(HcoState%Config%Err,MSG,SEP1='-' )
706 0 : MSG = ' - Use species:'
707 0 : CALL HCO_MSG(HcoState%Config%Err,MSG )
708 : ENDIF
709 :
710 : ! ----------------------------------------------------------------------
711 : ! Get species IDs and settings
712 : ! ----------------------------------------------------------------------
713 :
714 : ! # of species for which air-sea exchange will be calculated
715 0 : Inst%nOcSpc = 7 ! updated to include MENO3, ETNO3, MOH
716 :
717 : ! Initialize vector w/ species information
718 0 : ALLOCATE ( Inst%OcSpecs(Inst%nOcSpc) )
719 0 : DO I = 1, Inst%nOcSpc
720 0 : Inst%OcSpecs(I)%HcoID = -1
721 0 : Inst%OcSpecs(I)%OcSpcName = ''
722 0 : Inst%OcSpecs(I)%OcDataName = ''
723 0 : Inst%OcSpecs(I)%LiqVol = 0d0
724 0 : Inst%OcSpecs(I)%SCWPAR = 1
725 : ENDDO
726 :
727 : ! Counter
728 : I = 0
729 :
730 : ! ----------------------------------------------------------------------
731 : ! CH3I:
732 : ! ----------------------------------------------------------------------
733 :
734 0 : I = I + 1
735 0 : IF ( I > Inst%nOcSpc ) THEN
736 0 : CALL HCO_ERROR ( ERR, RC )
737 0 : RETURN
738 : ENDIF
739 :
740 0 : Inst%OcSpecs(I)%OcSpcName = 'CH3I'
741 0 : Inst%OcSpecs(I)%OcDataName = 'CH3I_SEAWATER'
742 0 : Inst%OcSpecs(I)%LiqVol = 1d0*7d0 + 3d0*7d0 + 1d0*38.5d0 ! Johnson, 2010
743 0 : Inst%OcSpecs(I)%SCWPAR = 1 ! Schmidt number following Johnson, 2010
744 :
745 : ! ----------------------------------------------------------------------
746 : ! DMS:
747 : ! ----------------------------------------------------------------------
748 :
749 0 : I = I + 1
750 0 : IF ( I > Inst%nOcSpc ) THEN
751 0 : CALL HCO_ERROR ( ERR, RC )
752 0 : RETURN
753 : ENDIF
754 :
755 0 : Inst%OcSpecs(I)%OcSpcName = 'DMS'
756 0 : Inst%OcSpecs(I)%OcDataName = 'DMS_SEAWATER'
757 0 : Inst%OcSpecs(I)%LiqVol = 2d0*7d0 + 6d0*7d0 + 1d0*21.0d0 ! Johnson, 2010
758 0 : Inst%OcSpecs(I)%SCWPAR = 2 ! Schmidt number following Saltzman et al., 1993
759 :
760 : ! ----------------------------------------------------------------------
761 : ! Acetone:
762 : ! ----------------------------------------------------------------------
763 :
764 0 : I = I + 1
765 0 : IF ( I > Inst%nOcSpc ) THEN
766 0 : CALL HCO_ERROR ( ERR, RC )
767 0 : RETURN
768 : ENDIF
769 :
770 0 : Inst%OcSpecs(I)%OcSpcName = 'ACET'
771 0 : Inst%OcSpecs(I)%OcDataName = 'ACET_SEAWATER'
772 0 : Inst%OcSpecs(I)%LiqVol = 3d0*7d0 + 6d0*7d0 + 1d0*7d0 + 1d0*7d0 ! Johnson, 2010
773 0 : Inst%OcSpecs(I)%SCWPAR = 3 ! Schmidt number of acetone
774 :
775 : ! ----------------------------------------------------------------------
776 : ! Methanol:
777 : ! ----------------------------------------------------------------------
778 :
779 0 : I = I + 1
780 0 : IF ( I > Inst%nOcSpc ) THEN
781 0 : CALL HCO_ERROR ( ERR, RC )
782 0 : RETURN
783 : ENDIF
784 :
785 0 : Inst%OcSpecs(I)%OcSpcName = 'MOH'
786 0 : Inst%OcSpecs(I)%OcDataName = 'MOH_SEAWATER'
787 0 : Inst%OcSpecs(I)%LiqVol = 1d0*7d0 + 4d0*7d0 + 1d0*7d0 ! Johnson, 2010
788 0 : Inst%OcSpecs(I)%SCWPAR = 1 ! Schmidt number of methanol
789 :
790 : ! ----------------------------------------------------------------------
791 : ! Acetaldehyde:
792 : ! ----------------------------------------------------------------------
793 :
794 0 : I = I + 1
795 0 : IF ( I > Inst%nOcSpc ) THEN
796 0 : CALL HCO_ERROR ( ERR, RC )
797 0 : RETURN
798 : ENDIF
799 :
800 0 : Inst%OcSpecs(I)%OcSpcName = 'ALD2'
801 0 : Inst%OcSpecs(I)%OcDataName = 'ALD2_SEAWATER'
802 0 : Inst%OcSpecs(I)%LiqVol = 2d0*7d0 + 4d0*7d0 + 1d0*7d0 + 1d0*7d0 ! Johnson, 2010
803 0 : Inst%OcSpecs(I)%SCWPAR = 4 ! Schmidt number of acetaldehyde
804 :
805 : ! ----------------------------------------------------------------------
806 : ! Methyl nitrate:
807 : ! ----------------------------------------------------------------------
808 :
809 0 : I = I + 1
810 0 : IF ( I > Inst%nOcSpc ) THEN
811 0 : CALL HCO_ERROR ( ERR, RC )
812 0 : RETURN
813 : ENDIF
814 :
815 0 : Inst%OcSpecs(I)%OcSpcName = 'MENO3'
816 0 : Inst%OcSpecs(I)%OcDataName = 'MENO3_SEAWATER'
817 0 : Inst%OcSpecs(I)%LiqVol = 64d0 ! Kornilov & Klselev 2015
818 0 : Inst%OcSpecs(I)%SCWPAR = 1
819 :
820 : ! ----------------------------------------------------------------------
821 : ! Ethyl nitrate:
822 : ! ----------------------------------------------------------------------
823 :
824 0 : I = I + 1
825 0 : IF ( I > Inst%nOcSpc ) THEN
826 0 : CALL HCO_ERROR ( ERR, RC )
827 0 : RETURN
828 : ENDIF
829 :
830 0 : Inst%OcSpecs(I)%OcSpcName = 'ETNO3'
831 0 : Inst%OcSpecs(I)%OcDataName = 'ETNO3_SEAWATER'
832 0 : Inst%OcSpecs(I)%LiqVol = 82.2d0 ! Kornilov & Klselev 2015
833 0 : Inst%OcSpecs(I)%SCWPAR = 1
834 :
835 : ! ----------------------------------------------------------------------
836 : ! Match module species with species assigned to this module in config.
837 : ! file
838 : ! ----------------------------------------------------------------------
839 :
840 : ! HEMCO species IDs of species names defined in config. file
841 0 : CALL HCO_GetExtHcoID( HcoState, ExtNr, HcoIDs, SpcNames, nSpc, RC )
842 0 : IF ( RC /= HCO_SUCCESS ) THEN
843 0 : CALL HCO_ERROR( 'ERROR 7', RC, THISLOC=LOC )
844 0 : RETURN
845 : ENDIF
846 :
847 : ! Set information in module variables
848 0 : DO I = 1, Inst%nOcSpc
849 :
850 : ! Append ocean tag '__OC' to this species name to make sure
851 : ! that we will also register non-tagged species.
852 0 : NAME_OC = TRIM(Inst%OcSpecs(I)%OcSpcName) // '__OC'
853 :
854 0 : DO J = 1, nSpc
855 :
856 : ! Compare model species names against defined module species.
857 : ! Also accept species names without the tag __OC, e.g.
858 : ! 'ACET' only instead of 'ACET__OC'.
859 0 : IF ( TRIM(SpcNames(J)) == TRIM(Inst%OcSpecs(I)%OcSpcName) .OR. &
860 0 : TRIM(SpcNames(J)) == TRIM(NAME_OC) ) THEN
861 0 : Inst%OcSpecs(I)%HcoID = HcoIDs(J)
862 0 : EXIT
863 : ENDIF
864 : ENDDO !J
865 :
866 : ! verbose
867 0 : IF ( Inst%OcSpecs(I)%HcoID > 0 .AND. HcoState%amIRoot ) THEN
868 0 : WRITE(MSG,*) ' - ', &
869 0 : TRIM(Inst%OcSpecs(I)%OcSpcName), Inst%OcSpecs(I)%HcoID
870 0 : CALL HCO_MSG(HcoState%Config%Err,MSG)
871 : ENDIF
872 : ENDDO !I
873 :
874 : ! Set met fields
875 0 : ExtState%U10M%DoUse = .TRUE.
876 0 : ExtState%V10M%DoUse = .TRUE.
877 0 : ExtState%TSKIN%DoUse = .TRUE.
878 0 : ExtState%FRLAND%DoUse = .TRUE.
879 0 : ExtState%FRLANDIC%DoUse = .TRUE.
880 0 : ExtState%FROCEAN%DoUse = .TRUE.
881 0 : ExtState%FRSEAICE%DoUse = .TRUE.
882 0 : ExtState%FRLAKE%DoUse = .TRUE.
883 0 : IF ( HcoState%Options%PBL_DRYDEP ) THEN
884 0 : ExtState%FRAC_OF_PBL%DoUse = .TRUE.
885 : ENDIF
886 : ! ExtState%FRCLND%DoUse = .TRUE.
887 :
888 : ! Enable extensions
889 : !ExtState%SeaFlux = .TRUE.
890 :
891 : ! Return w/ success
892 0 : IF ( ALLOCATED(HcoIDs ) ) DEALLOCATE(HcoIDs )
893 0 : IF ( ALLOCATED(SpcNames) ) DEALLOCATE(SpcNames)
894 0 : CALL HCO_LEAVE( HcoState%Config%Err,RC )
895 :
896 0 : END SUBROUTINE HCOX_SeaFlux_Init
897 : !EOC
898 : !------------------------------------------------------------------------------
899 : ! Harmonized Emissions Component (HEMCO) !
900 : !------------------------------------------------------------------------------
901 : !BOP
902 : !
903 : ! !IROUTINE: HCOX_SeaFlux_Final
904 : !
905 : ! !DESCRIPTION: Subroutine HCOX\_SeaFlux\_Final deallocates
906 : ! all module arrays.
907 : !\\
908 : !\\
909 : ! !INTERFACE:
910 : !
911 0 : SUBROUTINE HCOX_SeaFlux_Final( ExtState )
912 : !
913 : ! !INPUT PARAMETERS:
914 : !
915 : TYPE(Ext_State), POINTER :: ExtState ! Module options
916 : !
917 : ! !REVISION HISTORY:
918 : ! 16 Apr 2013 - C. Keller - Initial version
919 : ! See https://github.com/geoschem/hemco for complete history
920 : !EOP
921 : !------------------------------------------------------------------------------
922 : !BOC
923 : !
924 : !=================================================================
925 : ! HCOX_SeaFlux_Final begins here!
926 : !=================================================================
927 0 : CALL InstRemove( ExtState%SeaFlux )
928 :
929 : !IF ( ASSOCIATED( OcSpecs )) DEALLOCATE( OcSpecs )
930 :
931 0 : END SUBROUTINE HCOX_SeaFlux_Final
932 : !EOC
933 : !------------------------------------------------------------------------------
934 : ! Harmonized Emissions Component (HEMCO) !
935 : !------------------------------------------------------------------------------
936 : !BOP
937 : !
938 : ! !IROUTINE: InstGet
939 : !
940 : ! !DESCRIPTION: Subroutine InstGet returns a poiner to the desired instance.
941 : !\\
942 : !\\
943 : ! !INTERFACE:
944 : !
945 0 : SUBROUTINE InstGet ( Instance, Inst, RC, PrevInst )
946 : !
947 : ! !INPUT PARAMETERS:
948 : !
949 : INTEGER :: Instance
950 : TYPE(MyInst), POINTER :: Inst
951 : INTEGER :: RC
952 : TYPE(MyInst), POINTER, OPTIONAL :: PrevInst
953 : !
954 : ! !REVISION HISTORY:
955 : ! 18 Feb 2016 - C. Keller - Initial version
956 : ! See https://github.com/geoschem/hemco for complete history
957 : !EOP
958 : !------------------------------------------------------------------------------
959 : !BOC
960 : TYPE(MyInst), POINTER :: PrvInst
961 :
962 : !=================================================================
963 : ! InstGet begins here!
964 : !=================================================================
965 :
966 : ! Get instance. Also archive previous instance.
967 0 : PrvInst => NULL()
968 0 : Inst => AllInst
969 0 : DO WHILE ( ASSOCIATED(Inst) )
970 0 : IF ( Inst%Instance == Instance ) EXIT
971 0 : PrvInst => Inst
972 0 : Inst => Inst%NextInst
973 : END DO
974 0 : IF ( .NOT. ASSOCIATED( Inst ) ) THEN
975 0 : RC = HCO_FAIL
976 0 : RETURN
977 : ENDIF
978 :
979 : ! Pass output arguments
980 0 : IF ( PRESENT(PrevInst) ) PrevInst => PrvInst
981 :
982 : ! Cleanup & Return
983 0 : PrvInst => NULL()
984 0 : RC = HCO_SUCCESS
985 :
986 : END SUBROUTINE InstGet
987 : !EOC
988 : !------------------------------------------------------------------------------
989 : ! Harmonized Emissions Component (HEMCO) !
990 : !------------------------------------------------------------------------------
991 : !BOP
992 : !
993 : ! !IROUTINE: InstCreate
994 : !
995 : ! !DESCRIPTION: Subroutine InstCreate creates a new instance.
996 : !\\
997 : !\\
998 : ! !INTERFACE:
999 : !
1000 0 : SUBROUTINE InstCreate ( ExtNr, Instance, Inst, RC )
1001 : !
1002 : ! !INPUT PARAMETERS:
1003 : !
1004 : INTEGER, INTENT(IN) :: ExtNr
1005 : !
1006 : ! !OUTPUT PARAMETERS:
1007 : !
1008 : INTEGER, INTENT( OUT) :: Instance
1009 : TYPE(MyInst), POINTER :: Inst
1010 : !
1011 : ! !INPUT/OUTPUT PARAMETERS:
1012 : !
1013 : INTEGER, INTENT(INOUT) :: RC
1014 : !
1015 : ! !REVISION HISTORY:
1016 : ! 18 Feb 2016 - C. Keller - Initial version
1017 : ! See https://github.com/geoschem/hemco for complete history
1018 : !EOP
1019 : !------------------------------------------------------------------------------
1020 : !BOC
1021 : TYPE(MyInst), POINTER :: TmpInst
1022 : INTEGER :: nnInst
1023 :
1024 : !=================================================================
1025 : ! InstCreate begins here!
1026 : !=================================================================
1027 :
1028 : ! ----------------------------------------------------------------
1029 : ! Generic instance initialization
1030 : ! ----------------------------------------------------------------
1031 :
1032 : ! Initialize
1033 0 : Inst => NULL()
1034 :
1035 : ! Get number of already existing instances
1036 0 : TmpInst => AllInst
1037 0 : nnInst = 0
1038 :
1039 0 : DO WHILE ( ASSOCIATED(TmpInst) )
1040 0 : nnInst = nnInst + 1
1041 0 : TmpInst => TmpInst%NextInst
1042 : END DO
1043 :
1044 : ! Create new instance
1045 0 : ALLOCATE(Inst)
1046 0 : Inst%Instance = nnInst + 1
1047 0 : Inst%ExtNr = ExtNr
1048 :
1049 : ! Attach to instance list
1050 0 : Inst%NextInst => AllInst
1051 0 : AllInst => Inst
1052 :
1053 : ! Update output instance
1054 0 : Instance = Inst%Instance
1055 :
1056 : ! ----------------------------------------------------------------
1057 : ! Type specific initialization statements follow below
1058 : ! ----------------------------------------------------------------
1059 :
1060 : ! Return w/ success
1061 0 : RC = HCO_SUCCESS
1062 :
1063 0 : END SUBROUTINE InstCreate
1064 : !EOC
1065 : !------------------------------------------------------------------------------
1066 : ! Harmonized Emissions Component (HEMCO) !
1067 : !------------------------------------------------------------------------------
1068 : !BOP
1069 : !
1070 : ! !IROUTINE: InstRemove
1071 : !
1072 : ! !DESCRIPTION: Subroutine InstRemove creates a new instance.
1073 : !\\
1074 : !\\
1075 : ! !INTERFACE:
1076 : !
1077 0 : SUBROUTINE InstRemove ( Instance )
1078 : !
1079 : ! !INPUT PARAMETERS:
1080 : !
1081 : INTEGER :: Instance
1082 : !
1083 : ! !REVISION HISTORY:
1084 : ! 18 Feb 2016 - C. Keller - Initial version
1085 : ! See https://github.com/geoschem/hemco for complete history
1086 : !EOP
1087 : !------------------------------------------------------------------------------
1088 : !BOC
1089 : INTEGER :: RC
1090 : TYPE(MyInst), POINTER :: PrevInst
1091 : TYPE(MyInst), POINTER :: Inst
1092 :
1093 : !=================================================================
1094 : ! InstRemove begins here!
1095 : !=================================================================
1096 :
1097 : ! Init
1098 0 : PrevInst => NULL()
1099 0 : Inst => NULL()
1100 :
1101 : ! Get instance. Also archive previous instance.
1102 0 : CALL InstGet ( Instance, Inst, RC, PrevInst=PrevInst )
1103 :
1104 : ! Instance-specific deallocation
1105 0 : IF ( ASSOCIATED(Inst) ) THEN
1106 :
1107 : !---------------------------------------------------------------------
1108 : ! Deallocate fields of Inst before popping off from the list
1109 : ! in order to avoid memory leaks (Bob Yantosca (17 Aug 2022)
1110 : !---------------------------------------------------------------------
1111 0 : IF ( ASSOCIATED( Inst%OcSpecs ) ) THEN
1112 0 : DEALLOCATE( Inst%OcSpecs )
1113 : ENDIF
1114 0 : Inst%OcSpecs => NULL()
1115 :
1116 : !---------------------------------------------------------------------
1117 : ! Pop off instance from list
1118 : !---------------------------------------------------------------------
1119 0 : IF ( ASSOCIATED(PrevInst) ) THEN
1120 0 : PrevInst%NextInst => Inst%NextInst
1121 : ELSE
1122 0 : AllInst => Inst%NextInst
1123 : ENDIF
1124 0 : DEALLOCATE(Inst)
1125 : ENDIF
1126 :
1127 : ! Free pointers before exiting
1128 0 : PrevInst => NULL()
1129 0 : Inst => NULL()
1130 :
1131 0 : END SUBROUTINE InstRemove
1132 : !EOC
1133 0 : END MODULE HCOX_SeaFlux_Mod
1134 : !EOM
|