ROMS
Loading...
Searching...
No Matches
hypoxia_srm_mod.h
Go to the documentation of this file.
1 MODULE mod_biology
2!
3!git $Id$
4!================================================== Hernan G. Arango ===
5! Copyright (c) 2002-2025 The ROMS Group !
6! Licensed under a MIT/X style license !
7! See License_ROMS.md !
8!=======================================================================
9! !
10! Parameters for Hypoxia Simple Respiration Model: !
11! !
12! BioIter Maximum number of iterations to achieve convergence !
13! of the nonlinear solution. !
14! ResRate Total biological respiration rate (1/day). !
15! !
16!=======================================================================
17!
18 USE mod_param
19!
20 implicit none
21!
22! Set biological tracer identification indices.
23!
24 integer, allocatable :: idbio(:) ! Biological tracers
25
26 integer :: iOxyg ! Dissolved oxygen concentration
27 integer :: idresr ! total respiration rate
28!
29! Biological parameters.
30!
31 integer, allocatable :: bioiter(:)
32
33 real(r8), allocatable :: resrate(:) ! repiration rate (1/day)
34!
35 CONTAINS
36!
37 SUBROUTINE initialize_biology
38!
39!=======================================================================
40! !
41! This routine sets several variables needed by the biology model. !
42! It allocates and assigns biological tracers indices. !
43! !
44!=======================================================================
45!
46! Local variable declarations
47!
48 integer :: i, ic
49!
50!-----------------------------------------------------------------------
51! Set number of biological tracers.
52!-----------------------------------------------------------------------
53!
54 nbt=1
55
56#if defined DIAGNOSTICS && defined DIAGNOSTICS_BIO
57!
58!-----------------------------------------------------------------------
59! Set sources and sinks biology diagnostic parameters.
60!-----------------------------------------------------------------------
61!
62! Set number of diagnostics terms.
63!
64 ndbio2d=1
65 ndbio3d=0
66!
67! Initialize biology diagnostic indices.
68!
69 io2fx=1
70#endif
71!
72!-----------------------------------------------------------------------
73! Allocate various module variables.
74!-----------------------------------------------------------------------
75!
76 IF (.not.allocated(bioiter)) THEN
77 allocate ( bioiter(ngrids) )
78 dmem(1)=dmem(1)+real(ngrids,r8)
79 END IF
80
81 IF (.not.allocated(resrate)) THEN
82 allocate ( resrate(ngrids) )
83 dmem(1)=dmem(1)+real(ngrids,r8)
84 END IF
85!
86! Allocate biological tracer vector.
87!
88 IF (.not.allocated(idbio)) THEN
89 allocate ( idbio(nbt) )
90 dmem(1)=dmem(1)+real(nbt,r8)
91 END IF
92
93#if defined DIAGNOSTICS && defined DIAGNOSTICS_BIO
94!
95! Allocate biological diagnostics vectors
96!
97 IF (.not.allocated(idbio2)) THEN
98 allocate ( idbio2(ndbio2d) )
99 dmem(1)=dmem(1)+real(ndbio2d,r8)
100 END IF
101#endif
102!
103!-----------------------------------------------------------------------
104! Initialize tracer identification indices.
105!-----------------------------------------------------------------------
106!
107 ic=nat+npt+ncs+nns
108 DO i=1,nbt
109 idbio(i)=ic+i
110 END DO
111 ic=ic+1
112 ioxyg=ic
113!
114 RETURN
115 END SUBROUTINE initialize_biology
116
117 END MODULE mod_biology
real(r8), dimension(:), allocatable resrate
integer, dimension(:), allocatable bioiter
Definition ecosim_mod.h:343
integer, dimension(:), allocatable idbio2
Definition fennel_mod.h:105
subroutine initialize_biology
Definition ecosim_mod.h:499
integer io2fx
Definition fennel_mod.h:110
integer nat
Definition mod_param.F:499
integer ndbio2d
Definition mod_param.F:584
real(r8), dimension(:), allocatable dmem
Definition mod_param.F:137
integer ncs
Definition mod_param.F:525
integer nbt
Definition mod_param.F:509
integer ngrids
Definition mod_param.F:113
integer ndbio3d
Definition mod_param.F:585
integer nns
Definition mod_param.F:529
integer npt
Definition mod_param.F:505