/[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.4 by jmc, Tue Jul 13 18:03:31 2004 UTC revision 1.11 by stephd, Thu Dec 6 22:24:34 2007 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  #include "DIC_OPTIONS.h"  #include "DIC_OPTIONS.h"
5  #include "GCHEM_OPTIONS.h"  #include "GCHEM_OPTIONS.h"
6    
 #ifdef ALLOW_FE  
7  CStartOfInterFace  CStartOfInterFace
8        SUBROUTINE Fe_CHEM(        SUBROUTINE Fe_CHEM(
9       I           bi,bj,iMin,iMax,jMin,jMax,       I           bi,bj,iMin,iMax,jMin,jMax,
# Line 24  C     == GLobal variables == Line 23  C     == GLobal variables ==
23  #include "PARAMS.h"  #include "PARAMS.h"
24  #include "GRID.h"  #include "GRID.h"
25  #include "DIC_BIOTIC.h"  #include "DIC_BIOTIC.h"
 #include "PTRACERS_SIZE.h"  
 #include "PTRACERS.h"  
26    
27  C     == Routine arguments ==                  C     == Routine arguments ==                
28  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 35  C     myThid - Instance number for this Line 32  C     myThid - Instance number for this
32        _RL  fe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL  fe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
33        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
34        INTEGER myIter,myThid        INTEGER myIter,myThid
35    #ifdef AD_SAFE
36          _RL thx, thy, theps
37    #endif
38  CEndOfInterface  CEndOfInterface
39    
40    #ifdef ALLOW_FE
41    
42        INTEGER I,J,K        INTEGER I,J,K
43        _RL  lig, FeL        _RL  lig, FeL
44          _RL  tmpfe
45    
46  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
47  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
# Line 55  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC Line 57  CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
57  C ligand balance in surface layer  C ligand balance in surface layer
58  C in surface layer  C in surface layer
59    
60         DO j=jMin,jMax         DO j=jmin,jmax
61          DO i=iMin,iMax          DO i=imin,imax
62           DO k=1,nR           DO k=1,Nr
63            IF(hFacC(i,j,k,bi,bj) .gt. 0.0)THEN            IF (hFacC(i,j,k,bi,bj) .GT. 0. _d 0) THEN
64    
65  C   Ligand,FeL,Fe calculation  #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                lig=(-ligand_stab*fe (i,j,k,bi,bj)+  C   Ligand,FeL,Fe calculation
72       &              ligand_stab*ligand_tot-1                lig=(-ligand_stab*tmpfe +
73       &             +((ligand_stab*fe (i,j,k,bi,bj)       &              ligand_stab*ligand_tot-1. _d 0
74       &                -ligand_stab*ligand_tot+1)**2+4       &             +((ligand_stab*tmpfe
75       &                *ligand_stab*ligand_tot)**0.5)/(2*ligand_stab)       &                -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                FeL = ligand_tot-lig
80                freefe(i,j,k,bi,bj) = fe (i,j,k,bi,bj)-FeL                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              END IF  
100           ENDDO           ENDDO
101          ENDDO          ENDDO
102         ENDDO             ENDDO    
103  c  c
104    #endif
105          RETURN          RETURN
106          END                                END
 #endif  

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22