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

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

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

revision 1.9 by stephd, Tue Nov 28 21:16:03 2006 UTC revision 1.13 by dfer, Mon Apr 7 20:31:16 2008 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "DIC_OPTIONS.h"  #include "DIC_OPTIONS.h"
 #include "GCHEM_OPTIONS.h"  
5    
6  CStartOfInterFace  CStartOfInterFace
7        SUBROUTINE Fe_CHEM(        SUBROUTINE Fe_CHEM(
# Line 22  C     == GLobal variables == Line 21  C     == GLobal variables ==
21  #include "EEPARAMS.h"  #include "EEPARAMS.h"
22  #include "PARAMS.h"  #include "PARAMS.h"
23  #include "GRID.h"  #include "GRID.h"
24  #include "DIC_BIOTIC.h"  #include "DIC_VARS.h"
25    
26  C     == Routine arguments ==                  C     == Routine arguments ==                
27  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
# Line 41  CEndOfInterface Line 40  CEndOfInterface
40    
41        INTEGER I,J,K        INTEGER I,J,K
42        _RL  lig, FeL        _RL  lig, FeL
43          _RL  tmpfe
44    
45  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
46  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
# Line 58  C in surface layer Line 58  C in surface layer
58    
59         DO j=jmin,jmax         DO j=jmin,jmax
60          DO i=imin,imax          DO i=imin,imax
61           DO k=1,nR           DO k=1,Nr
62            IF(hFacC(i,j,k,bi,bj) .gt. 0.0)THEN            IF (hFacC(i,j,k,bi,bj) .GT. 0. _d 0) THEN
63    
64  C   Ligand,FeL,Fe calculation  #ifdef DIC_NO_NEG
65                  tmpfe=max(0. _d0 , fe (i,j,k,bi,bj))
66    #else
67                  tmpfe=fe (i,j,k,bi,bj)
68    #endif
69                            
70                lig=(-ligand_stab*fe (i,j,k,bi,bj)+  C   Ligand,FeL,Fe calculation
71       &              ligand_stab*ligand_tot-1                lig=(-ligand_stab*tmpfe +
72       &             +((ligand_stab*fe (i,j,k,bi,bj)       &              ligand_stab*ligand_tot-1. _d 0
73       &                -ligand_stab*ligand_tot+1)**2+4       &             +((ligand_stab*tmpfe
74       &                *ligand_stab*ligand_tot)**0.5)/(2*ligand_stab)       &                -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    
78                FeL = ligand_tot-lig                FeL = ligand_tot-lig
79                freefe(i,j,k,bi,bj) = fe (i,j,k,bi,bj)-FeL                if (tmpfe.eq.0. _d 0) then
80                    freefe(i,j,k,bi,bj) = tmpfe -FeL
81                  else
82                    freefe(i,j,k,bi,bj) = 0. _d 0
83                  endif
84  #ifdef MINFE  #ifdef MINFE
85  #ifdef AD_SAFE  #ifdef AD_SAFE
86                thx=freefe(i,j,k,bi,bj)                thx=freefe(i,j,k,bi,bj)
87                thy=freefemax                thy=freefemax
88                theps=1.d-8                theps=1. _d -8
89                freefe(i,j,k,bi,bj) =                freefe(i,j,k,bi,bj) =
90       &                 ( 1.d0 - tanh((thx-thy)/theps) ) * thx/2 +       &                 ( 1. _d 0 - tanh((thx-thy)/theps) ) * thx/2.+
91       &                 ( 1.d0 + tanh((thx-thy)/theps) ) * thy/2       &                 ( 1. _d 0 + tanh((thx-thy)/theps) ) * thy/2.
92    
93  #else  #else
94                freefe(i,j,k,bi,bj) = min(freefe(i,j,k,bi,bj),freefemax)                freefe(i,j,k,bi,bj) = min(freefe(i,j,k,bi,bj),freefemax)
# Line 92  C   Ligand,FeL,Fe calculation Line 102  C   Ligand,FeL,Fe calculation
102  c  c
103  #endif  #endif
104          RETURN          RETURN
105          END                                END

Legend:
Removed from v.1.9  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22