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

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

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


Revision 1.8 - (hide annotations) (download)
Fri Dec 16 21:07:53 2005 UTC (18 years, 5 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint58r_post, checkpoint58n_post, checkpoint58h_post, checkpoint58q_post, checkpoint58j_post, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58k_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.7: +3 -3 lines
o dic code now does no calculations on the overlap regions

1 stephd 1.8 C $Header: /u/gcmpack/MITgcm/pkg/dic/fe_chem.F,v 1.7 2005/12/12 19:07:36 stephd Exp $
2 jmc 1.4 C $Name: $
3    
4 edhill 1.3 #include "DIC_OPTIONS.h"
5 stephd 1.1 #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 jmc 1.4 #include "PTRACERS_SIZE.h"
27 stephd 1.1 #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 jmc 1.5 #ifdef ALLOW_FE
40 stephd 1.1
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 stephd 1.8 DO j=jmin,jmax
59     DO i=imin,imax
60 stephd 1.1 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 stephd 1.6 #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 stephd 1.1 END IF
78     ENDDO
79     ENDDO
80     ENDDO
81     c
82 jmc 1.5 #endif
83 stephd 1.1 RETURN
84     END

  ViewVC Help
Powered by ViewVC 1.1.22