/[MITgcm]/MITgcm/pkg/dic/fe_chem.F
ViewVC logotype

Annotation of /MITgcm/pkg/dic/fe_chem.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.11 - (hide annotations) (download)
Thu Dec 6 22:24:34 2007 UTC (17 years, 7 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n
Changes since 1.10: +15 -5 lines
o don't allow negative biological activity (even if the nutrients have
  become negative). Need new GCHEM_OPTIONS.h macro: #define DIC_NO_NEG.

1 stephd 1.11 C $Header: /u/gcmpack/MITgcm/pkg/dic/fe_chem.F,v 1.10 2007/10/26 21:08:13 dfer Exp $
2 jmc 1.4 C $Name: $
3    
4 edhill 1.3 #include "DIC_OPTIONS.h"
5 stephd 1.1 #include "GCHEM_OPTIONS.h"
6    
7     CStartOfInterFace
8     SUBROUTINE Fe_CHEM(
9     I bi,bj,iMin,iMax,jMin,jMax,
10     I fe, freefe,
11     I myIter, myThid )
12     C /==========================================================\
13     C | SUBROUTINE Fe_chem |
14     C | |
15     C | o Calculate L,FeL,Fe concentration |
16     C |==========================================================|
17     IMPLICIT NONE
18    
19     C == GLobal variables ==
20     #include "SIZE.h"
21     #include "DYNVARS.h"
22     #include "EEPARAMS.h"
23     #include "PARAMS.h"
24     #include "GRID.h"
25     #include "DIC_BIOTIC.h"
26    
27     C == Routine arguments ==
28     C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
29     C results will be set.
30     C myThid - Instance number for this innvocation of CALC_GT
31     _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
32     _RL fe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
33     INTEGER bi,bj,iMin,iMax,jMin,jMax
34     INTEGER myIter,myThid
35 stephd 1.9 #ifdef AD_SAFE
36     _RL thx, thy, theps
37     #endif
38 stephd 1.1 CEndOfInterface
39    
40 jmc 1.5 #ifdef ALLOW_FE
41 stephd 1.1
42     INTEGER I,J,K
43     _RL lig, FeL
44 stephd 1.11 _RL tmpfe
45 stephd 1.1
46     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
47     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
48     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
49     CC
50     CC ADAPTED FROM PAYAL
51     CC
52     CC
53     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
54     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
55     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
56    
57     C ligand balance in surface layer
58     C in surface layer
59    
60 stephd 1.8 DO j=jmin,jmax
61     DO i=imin,imax
62 dfer 1.10 DO k=1,Nr
63     IF (hFacC(i,j,k,bi,bj) .GT. 0. _d 0) THEN
64 stephd 1.1
65 stephd 1.11 #ifdef DIC_NO_NEG
66     tmpfe=max(0. _d0 , fe (i,j,k,bi,bj))
67     #else
68     tmpfe=fe (i,j,k,bi,bj)
69     #endif
70    
71 stephd 1.1 C Ligand,FeL,Fe calculation
72 stephd 1.11 lig=(-ligand_stab*tmpfe +
73 dfer 1.10 & ligand_stab*ligand_tot-1. _d 0
74 stephd 1.11 & +((ligand_stab*tmpfe
75 dfer 1.10 & -ligand_stab*ligand_tot+1. _d 0)**2
76     & +4. _d 0*ligand_stab*ligand_tot)**0.5 _d 0
77     & )/(2. _d 0*ligand_stab)
78 stephd 1.1
79     FeL = ligand_tot-lig
80 stephd 1.11 if (tmpfe.eq.0. _d 0) then
81     freefe(i,j,k,bi,bj) = tmpfe -FeL
82     else
83     freefe(i,j,k,bi,bj) = 0. _d 0
84     endif
85 stephd 1.6 #ifdef MINFE
86 stephd 1.9 #ifdef AD_SAFE
87     thx=freefe(i,j,k,bi,bj)
88     thy=freefemax
89 dfer 1.10 theps=1. _d -8
90 stephd 1.9 freefe(i,j,k,bi,bj) =
91 dfer 1.10 & ( 1. _d 0 - tanh((thx-thy)/theps) ) * thx/2.+
92     & ( 1. _d 0 + tanh((thx-thy)/theps) ) * thy/2.
93 stephd 1.9
94     #else
95 stephd 1.6 freefe(i,j,k,bi,bj) = min(freefe(i,j,k,bi,bj),freefemax)
96 stephd 1.9 #endif
97 stephd 1.6 fe(i,j,k,bi,bj) = FeL+freefe(i,j,k,bi,bj)
98     #endif
99 stephd 1.1 END IF
100     ENDDO
101     ENDDO
102     ENDDO
103     c
104 jmc 1.5 #endif
105 stephd 1.1 RETURN
106 dfer 1.10 END

  ViewVC Help
Powered by ViewVC 1.1.22