/[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.15 - (hide annotations) (download)
Mon Jun 23 22:26:32 2008 UTC (17 years ago) by stephd
Branch: MAIN
CVS Tags: checkpoint61, checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62d, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.14: +2 -2 lines
o correct bug - which was losing iron!

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

  ViewVC Help
Powered by ViewVC 1.1.22