/[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.10 - (hide annotations) (download)
Fri Oct 26 21:08:13 2007 UTC (17 years, 8 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint59k, checkpoint59j
Changes since 1.9: +11 -10 lines
Add tons of "_d 0" (which changes the outputs)

1 dfer 1.10 C $Header: /u/gcmpack/MITgcm/pkg/dic/fe_chem.F,v 1.9 2006/11/28 21:16:03 stephd 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    
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     C Ligand,FeL,Fe calculation
65    
66     lig=(-ligand_stab*fe (i,j,k,bi,bj)+
67 dfer 1.10 & ligand_stab*ligand_tot-1. _d 0
68 stephd 1.1 & +((ligand_stab*fe (i,j,k,bi,bj)
69 dfer 1.10 & -ligand_stab*ligand_tot+1. _d 0)**2
70     & +4. _d 0*ligand_stab*ligand_tot)**0.5 _d 0
71     & )/(2. _d 0*ligand_stab)
72 stephd 1.1
73     FeL = ligand_tot-lig
74     freefe(i,j,k,bi,bj) = fe (i,j,k,bi,bj)-FeL
75 stephd 1.6 #ifdef MINFE
76 stephd 1.9 #ifdef AD_SAFE
77     thx=freefe(i,j,k,bi,bj)
78     thy=freefemax
79 dfer 1.10 theps=1. _d -8
80 stephd 1.9 freefe(i,j,k,bi,bj) =
81 dfer 1.10 & ( 1. _d 0 - tanh((thx-thy)/theps) ) * thx/2.+
82     & ( 1. _d 0 + tanh((thx-thy)/theps) ) * thy/2.
83 stephd 1.9
84     #else
85 stephd 1.6 freefe(i,j,k,bi,bj) = min(freefe(i,j,k,bi,bj),freefemax)
86 stephd 1.9 #endif
87 stephd 1.6 fe(i,j,k,bi,bj) = FeL+freefe(i,j,k,bi,bj)
88     #endif
89 stephd 1.1 END IF
90     ENDDO
91     ENDDO
92     ENDDO
93     c
94 jmc 1.5 #endif
95 stephd 1.1 RETURN
96 dfer 1.10 END

  ViewVC Help
Powered by ViewVC 1.1.22