/[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.6 - (show annotations) (download)
Thu Oct 13 16:25:12 2005 UTC (19 years, 9 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint57v_post, checkpoint57y_post, checkpoint57y_pre, checkpoint57x_post, checkpoint57w_post
Changes since 1.5: +5 -1 lines
o add additional switches MINFE - to limit amount of free iron
                          READ_PAR - reads PAR from file, rather
                             than using insol.F

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/fe_chem.F,v 1.5 2004/10/18 16:01:13 jmc 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 #include "PTRACERS_SIZE.h"
27 #include "PTRACERS.h"
28
29 C == Routine arguments ==
30 C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
31 C results will be set.
32 C myThid - Instance number for this innvocation of CALC_GT
33 _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
34 _RL fe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
35 INTEGER bi,bj,iMin,iMax,jMin,jMax
36 INTEGER myIter,myThid
37 CEndOfInterface
38
39 #ifdef ALLOW_FE
40
41 INTEGER I,J,K
42 _RL lig, FeL
43
44 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
45 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
46 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
47 CC
48 CC ADAPTED FROM PAYAL
49 CC
50 CC
51 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
52 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
53 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCc
54
55 C ligand balance in surface layer
56 C in surface layer
57
58 DO j=jMin,jMax
59 DO i=iMin,iMax
60 DO k=1,nR
61 IF(hFacC(i,j,k,bi,bj) .gt. 0.0)THEN
62
63 C Ligand,FeL,Fe calculation
64
65 lig=(-ligand_stab*fe (i,j,k,bi,bj)+
66 & ligand_stab*ligand_tot-1
67 & +((ligand_stab*fe (i,j,k,bi,bj)
68 & -ligand_stab*ligand_tot+1)**2+4
69 & *ligand_stab*ligand_tot)**0.5)/(2*ligand_stab)
70
71 FeL = ligand_tot-lig
72 freefe(i,j,k,bi,bj) = fe (i,j,k,bi,bj)-FeL
73 #ifdef MINFE
74 freefe(i,j,k,bi,bj) = min(freefe(i,j,k,bi,bj),freefemax)
75 fe(i,j,k,bi,bj) = FeL+freefe(i,j,k,bi,bj)
76 #endif
77 END IF
78 ENDDO
79 ENDDO
80 ENDDO
81 c
82 #endif
83 RETURN
84 END

  ViewVC Help
Powered by ViewVC 1.1.22