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

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

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


Revision 1.12 - (show annotations) (download)
Fri Apr 4 21:37:06 2008 UTC (17 years, 3 months ago) by dfer
Branch: MAIN
Changes since 1.11: +2 -2 lines
Merging DIC_ABIOTIC.h and DIC_BIOTIC.h

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/fe_chem.F,v 1.11 2007/12/06 22:24:34 stephd Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5 #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_VARS.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 #ifdef AD_SAFE
36 _RL thx, thy, theps
37 #endif
38 CEndOfInterface
39
40 #ifdef ALLOW_FE
41
42 INTEGER I,J,K
43 _RL lig, FeL
44 _RL tmpfe
45
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 DO j=jmin,jmax
61 DO i=imin,imax
62 DO k=1,Nr
63 IF (hFacC(i,j,k,bi,bj) .GT. 0. _d 0) THEN
64
65 #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 C Ligand,FeL,Fe calculation
72 lig=(-ligand_stab*tmpfe +
73 & ligand_stab*ligand_tot-1. _d 0
74 & +((ligand_stab*tmpfe
75 & -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
79 FeL = ligand_tot-lig
80 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 #ifdef MINFE
86 #ifdef AD_SAFE
87 thx=freefe(i,j,k,bi,bj)
88 thy=freefemax
89 theps=1. _d -8
90 freefe(i,j,k,bi,bj) =
91 & ( 1. _d 0 - tanh((thx-thy)/theps) ) * thx/2.+
92 & ( 1. _d 0 + tanh((thx-thy)/theps) ) * thy/2.
93
94 #else
95 freefe(i,j,k,bi,bj) = min(freefe(i,j,k,bi,bj),freefemax)
96 #endif
97 fe(i,j,k,bi,bj) = FeL+freefe(i,j,k,bi,bj)
98 #endif
99 END IF
100 ENDDO
101 ENDDO
102 ENDDO
103 c
104 #endif
105 RETURN
106 END

  ViewVC Help
Powered by ViewVC 1.1.22