/[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.1.2.1 - (show annotations) (download)
Thu Oct 2 18:30:07 2003 UTC (21 years, 9 months ago) by adcroft
Branch: branch-genmake2
Changes since 1.1: +1 -1 lines
Mis-type CONFIG as CONF !!!

1 #include "DIC_OPTIONS.h"
2 #include "GCHEM_OPTIONS.h"
3
4 CStartOfInterFace
5 SUBROUTINE Fe_CHEM(
6 I bi,bj,iMin,iMax,jMin,jMax,
7 I fe, freefe,
8 I myIter, myThid )
9 C /==========================================================\
10 C | SUBROUTINE Fe_chem |
11 C | |
12 C | o Calculate L,FeL,Fe concentration |
13 C |==========================================================|
14 IMPLICIT NONE
15
16 C == GLobal variables ==
17 #include "SIZE.h"
18 #include "DYNVARS.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "GRID.h"
22 #include "DIC_BIOTIC.h"
23 #include "PTRACERS.h"
24
25 C == Routine arguments ==
26 C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
27 C results will be set.
28 C myThid - Instance number for this innvocation of CALC_GT
29 _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
30 _RL fe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
31 INTEGER bi,bj,iMin,iMax,jMin,jMax
32 INTEGER myIter,myThid
33 CEndOfInterface
34
35
36 INTEGER I,J,K
37 _RL lig, FeL
38
39 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
40 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
41 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
42 CC
43 CC ADAPTED FROM PAYAL
44 CC
45 CC
46 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
47 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
48 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
49
50 C ligand balance in surface layer
51 C in surface layer
52
53 DO j=jMin,jMax
54 DO i=iMin,iMax
55 DO k=1,nR
56 IF(hFacC(i,j,k,bi,bj) .gt. 0.0)THEN
57
58 C Ligand,FeL,Fe calculation
59
60 lig=(-ligand_stab*fe (i,j,k,bi,bj)+
61 & ligand_stab*ligand_tot-1
62 & +((ligand_stab*fe (i,j,k,bi,bj)
63 & -ligand_stab*ligand_tot+1)**2+4
64 & *ligand_stab*ligand_tot)**0.5)/(2*ligand_stab)
65
66 FeL = ligand_tot-lig
67 freefe(i,j,k,bi,bj) = fe (i,j,k,bi,bj)-FeL
68 END IF
69 ENDDO
70 ENDDO
71 ENDDO
72 c
73 RETURN
74 END
75

  ViewVC Help
Powered by ViewVC 1.1.22