/[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.9 - (show annotations) (download)
Tue Nov 28 21:16:03 2006 UTC (18 years, 7 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58x_post, checkpoint58t_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59i, checkpoint59h, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post
Changes since 1.8: +14 -3 lines
o changes to make dic code more adjoint friendly:
      - standardize how tracers are passed from dic_biotic_forcing to
        other subroutines
      - add a tanh function to take the place of min(x,y) in bio_export.F
        and fe_chem.F.

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/fe_chem.F,v 1.8 2005/12/16 21:07:53 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_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 #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
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 DO j=jmin,jmax
60 DO i=imin,imax
61 DO k=1,nR
62 IF(hFacC(i,j,k,bi,bj) .gt. 0.0)THEN
63
64 C Ligand,FeL,Fe calculation
65
66 lig=(-ligand_stab*fe (i,j,k,bi,bj)+
67 & ligand_stab*ligand_tot-1
68 & +((ligand_stab*fe (i,j,k,bi,bj)
69 & -ligand_stab*ligand_tot+1)**2+4
70 & *ligand_stab*ligand_tot)**0.5)/(2*ligand_stab)
71
72 FeL = ligand_tot-lig
73 freefe(i,j,k,bi,bj) = fe (i,j,k,bi,bj)-FeL
74 #ifdef MINFE
75 #ifdef AD_SAFE
76 thx=freefe(i,j,k,bi,bj)
77 thy=freefemax
78 theps=1.d-8
79 freefe(i,j,k,bi,bj) =
80 & ( 1.d0 - tanh((thx-thy)/theps) ) * thx/2 +
81 & ( 1.d0 + tanh((thx-thy)/theps) ) * thy/2
82
83 #else
84 freefe(i,j,k,bi,bj) = min(freefe(i,j,k,bi,bj),freefemax)
85 #endif
86 fe(i,j,k,bi,bj) = FeL+freefe(i,j,k,bi,bj)
87 #endif
88 END IF
89 ENDDO
90 ENDDO
91 ENDDO
92 c
93 #endif
94 RETURN
95 END

  ViewVC Help
Powered by ViewVC 1.1.22