/[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.17 - (hide annotations) (download)
Wed Aug 22 00:40:56 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63s, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.16: +11 -2 lines
move full initialisation of freefe array from dic_biotic_forcing.F to fe_chem.F:
 - more logical (output arg. array of S/R FE_CHEM is defined everywhere)
 - prevents TAF to drop the initialisation in TLM code

1 jmc 1.17 C $Header: /u/gcmpack/MITgcm/pkg/dic/fe_chem.F,v 1.16 2010/04/13 03:06:14 jmc Exp $
2 jmc 1.4 C $Name: $
3    
4 edhill 1.3 #include "DIC_OPTIONS.h"
5 stephd 1.1
6 jmc 1.16 CBOP
7     C !ROUTINE: Fe_CHEM
8     C !INTERFACE:
9 stephd 1.1 SUBROUTINE Fe_CHEM(
10 jmc 1.16 I bi,bj, iMin,iMax,jMin,jMax,
11 jmc 1.17 I fe,
12     O freefe,
13 stephd 1.1 I myIter, myThid )
14 jmc 1.16
15     C !DESCRIPTION: \bv
16     C *==========================================================*
17     C | SUBROUTINE Fe_CHEM
18     C | o Calculate L,FeL,Fe concentration
19     C *==========================================================*
20     C \ev
21    
22     C !USES:
23 stephd 1.1 IMPLICIT NONE
24    
25     C == GLobal variables ==
26     #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "GRID.h"
30 dfer 1.12 #include "DIC_VARS.h"
31 stephd 1.1
32 jmc 1.16 C !INPUT/OUTPUT PARAMETERS:
33     C == Routine arguments ==
34     C bi, bj :: current tile indices
35     C iMin,iMax,jMin,jMax :: Range of points for which calculation is performed.
36     C myThid :: my Thread Id number
37     INTEGER bi,bj
38     INTEGER iMin,iMax,jMin,jMax
39     _RL fe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
40     _RL freefe(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
41     INTEGER myIter, myThid
42     CEOP
43 stephd 1.1
44 jmc 1.5 #ifdef ALLOW_FE
45 jmc 1.16 C !LOCAL VARIABLES:
46     INTEGER i,j,k
47 stephd 1.1 _RL lig, FeL
48 stephd 1.11 _RL tmpfe
49 jmc 1.16 #ifdef AD_SAFE
50     _RL thx, thy, theps
51     #endif
52 stephd 1.1
53 jmc 1.16 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
54     C
55     C ADAPTED FROM PAYAL
56     C
57     CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
58 stephd 1.1
59 jmc 1.17 DO k=1,Nr
60     DO j=1-OLy,sNy+OLy
61     DO i=1-OLx,sNx+OLx
62     freefe(i,j,k) = 0. _d 0
63     ENDDO
64     ENDDO
65     ENDDO
66    
67 stephd 1.1 C ligand balance in surface layer
68     C in surface layer
69    
70 jmc 1.16 DO k=1,Nr
71     DO j=jMin,jMax
72     DO i=iMin,iMax
73     IF ( maskC(i,j,k,bi,bj).GT.0. ) THEN
74 stephd 1.1
75 stephd 1.11 #ifdef DIC_NO_NEG
76 jmc 1.16 tmpfe =MAX( 0. _d 0 , fe(i,j,k) )
77 stephd 1.11 #else
78 jmc 1.16 tmpfe = fe(i,j,k)
79 stephd 1.11 #endif
80 jmc 1.16
81 stephd 1.1 C Ligand,FeL,Fe calculation
82 stephd 1.11 lig=(-ligand_stab*tmpfe +
83 dfer 1.10 & ligand_stab*ligand_tot-1. _d 0
84 jmc 1.16 & +((ligand_stab*tmpfe
85 dfer 1.10 & -ligand_stab*ligand_tot+1. _d 0)**2
86     & +4. _d 0*ligand_stab*ligand_tot)**0.5 _d 0
87     & )/(2. _d 0*ligand_stab)
88 jmc 1.16
89 stephd 1.1 FeL = ligand_tot-lig
90 jmc 1.16 IF (tmpfe.NE.0. _d 0) THEN
91     freefe(i,j,k) = tmpfe -FeL
92     ELSE
93     freefe(i,j,k) = 0. _d 0
94     ENDIF
95 stephd 1.6 #ifdef MINFE
96 stephd 1.9 #ifdef AD_SAFE
97 jmc 1.16 thx=freefe(i,j,k)
98 stephd 1.9 thy=freefemax
99 dfer 1.10 theps=1. _d -8
100 jmc 1.16 freefe(i,j,k) =
101 dfer 1.10 & ( 1. _d 0 - tanh((thx-thy)/theps) ) * thx/2.+
102     & ( 1. _d 0 + tanh((thx-thy)/theps) ) * thy/2.
103 stephd 1.9
104     #else
105 jmc 1.16 freefe(i,j,k) = MIN(freefe(i,j,k),freefemax)
106 stephd 1.9 #endif
107 jmc 1.16 fe(i,j,k) = FeL+freefe(i,j,k)
108 stephd 1.6 #endif
109 jmc 1.16 ENDIF
110 stephd 1.1 ENDDO
111     ENDDO
112 jmc 1.16 ENDDO
113    
114     #endif /* ALLOW_FE */
115     RETURN
116     END

  ViewVC Help
Powered by ViewVC 1.1.22