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

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

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


Revision 1.5 - (hide annotations) (download)
Fri Oct 26 21:08:12 2007 UTC (16 years, 6 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59k, checkpoint59j
Changes since 1.4: +7 -7 lines
Add tons of "_d 0" (which changes the outputs)

1 dfer 1.5 C $Header: /u/gcmpack/MITgcm/pkg/dic/calcite_saturation.F,v 1.4 2007/10/09 00:01:42 jmc Exp $
2 jmc 1.4 C $Name: $
3    
4 stephd 1.1 #include "DIC_OPTIONS.h"
5     #include "GCHEM_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: CAR_FLUX
9    
10     C !INTERFACE: ==========================================================
11 stephd 1.3 SUBROUTINE CALCITE_SATURATION(PTR_DIC, PTR_ALK, PTR_PO4,
12 stephd 1.1 I bi,bj,imin,imax,jmin,jmax,
13     I myIter,myTime,myThid)
14    
15     C !DESCRIPTION:
16     C Calculate carbonate fluxes
17    
18     C !USES: ===============================================================
19     IMPLICIT NONE
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 "DIC_ABIOTIC.h"
27    
28     C !INPUT PARAMETERS: ===================================================
29     C myThid :: thread number
30     C myIter :: current timestep
31     C myTime :: current time
32     C bioac :: biological productivity
33 stephd 1.3 _RL PTR_DIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
34     _RL PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
35     _RL PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
36    
37 stephd 1.1 INTEGER myIter
38     _RL myTime
39     INTEGER myThid
40     INTEGER imin, imax, jmin, jmax, bi, bj
41    
42     C !OUTPUT PARAMETERS: ===================================================
43    
44     #ifdef ALLOW_PTRACERS
45     #ifdef DIC_BIOTIC
46    
47     C !LOCAL VARIABLES: ====================================================
48     C i,j,k :: loop indices
49     c ko :: loop-within-loop index
50     c depth_u, depth_l :: depths of upper and lower interfaces
51     c flux_u, flux_l :: flux through upper and lower interfaces
52     c zbase :: depth of bottom of current productive layer
53     INTEGER I,J,k
54     _RL carbonate
55     _RL calcium
56     _RL silicaTEST
57     _RL po4local
58     _RL diclocal
59     _RL alklocal
60     _RL pCO2local
61     _RL pHlocal
62     INTEGER CO3ITER
63     INTEGER CO3ITERmax
64     CEOP
65    
66    
67     cmick...................................................
68     write(6,*)'myIter ',myIter,' CALLED CALCITEcd_SATURATION'
69     c write(6,*)'WARNING calcite_sat needs 3d silica & H0 set=7.9'
70     c write(6,*)' - & Fixed first guess of deep pH to 7.9'
71     cmick....................................................
72    
73     c determine carbonate ion concentration through full domain
74     c determine calcite saturation state
75 dfer 1.5 DO k=1,Nr
76 stephd 1.1
77     CALL CARBON_COEFFS_PRESSURE_DEP(
78     I theta,salt,
79     I bi,bj,iMin,iMax,jMin,jMax,
80     I k)
81    
82    
83 stephd 1.2 DO j=jmin,jmax
84     DO i=imin,imax
85 stephd 1.1
86 dfer 1.5 if ( hFacC(i,j,k,bi,bj) .gt. 0. _d 0 ) then
87 stephd 1.1
88 dfer 1.5 calcium = 1.028 _d -2*salt(i,j,k,bi,bj)/35. _d 0
89 stephd 1.1
90     c 30 micromol = 0.03 mol m-3
91 dfer 1.5 silicaTEST = 0.03 _d 0
92 stephd 1.3 po4local = PTR_PO4(i,j,k)
93     diclocal = PTR_DIC(i,j,k)
94     alklocal = PTR_ALK(i,j,k)
95 stephd 1.1 c pHlocal = pHlast(i,j,k,bi,bj)
96 dfer 1.5 pHlocal = 7.9 _d 0
97 stephd 1.1
98     CMICK - TEMPORARY!!!!!
99     CMICK silica = fixed
100     CMICK silica = fixed
101     C
102     CMICK -DEC 04
103     CMICK- NOW ITERATE pH SOLVER AT DEPTH ONLY
104     CMICK TO ENSURE ACCURATE ESTIMATE OF CO3 AT DEPTH
105     CMICK - NOTE Si STILL USING A UNIFORM DUMMY VALUE
106     CO3itermax = 10
107     CMICK - SO NOW WE ITERATE, UPDATING THE ESTIMATE OF pH and CO3--
108     CMICK - SINCE WE CALL THIS FOR DEEP OCEAN INFREQUENTLY (MONTHLY?)
109     CMIKC - CAN AFFORD TO MAKE SEVERAL ITERATIONS...
110     DO CO3iter = 1, CO3itermax
111     CALL CALC_PCO2_APPROX_CO3(
112     I theta(i,j,k,bi,bj),salt(i,j,k,bi,bj),
113     I diclocal, po4local,
114     I silicaTEST,alklocal,
115     I ak1(i,j,bi,bj),ak2(i,j,bi,bj),
116     I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj),
117     I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
118     I aksi(i,j,bi,bj),akf(i,j,bi,bj),ff(i,j,bi,bj),
119     I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj),
120     U pHlocal,pCO2local,
121     U carbonate )
122     c........................................................
123     c if(i .eq. 76 .and. j .eq. 36 .and. k .eq. 15) then
124     c write(6,*)'Iteration, pH = ',CO3iter,pHlocal
125     c endif
126     c........................................................
127     END DO
128    
129    
130     omegaC(i,j,k,bi,bj) = calcium * carbonate /
131     & Ksp_TP_Calc(i,j,bi,bj)
132    
133     cmick...................................................
134     c if(omegaC(i,j,k,bi,bj) .eq. 0.) then
135     c if(i .eq. 76 .and. j .eq. 36 .and. k .eq. 15) then
136     c write(6,*)'i,j,k,KS,CO3,pHCa,T,S,hfacc,omega',
137     c & i,j,k,
138     c & Ksp_TP_Calc(i,j,bi,bj),
139     c & carbonate,calcium,pHlocal,
140     c & theta(i,j,k,bi,bj),salt(i,j,k,bi,bj),
141     c & hfacc(i,j,k,bi,bj),omegaC(i,j,k,bi,bj)
142     c write(6,*)'Ksp_TP_Calc',
143     c & Ksp_TP_Calc(i,j,bi,bj)
144     c write(6,*)'dic, alk, po4 ',
145     c & diclocal, alklocal,po4local
146     c write(6,*)'k1, k2, k1p, k2p, k3p ',
147     c & ak1(i,j,bi,bj),ak2(i,j,bi,bj),
148     c & ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj)
149     c write(6,*)'ks, kb, kw, ksi ',
150     c & aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
151     c & aksi(i,j,bi,bj)
152     c write(6,*)'akf, ff, bt, st, ft ',
153     c & akf(i,j,bi,bj),ff(i,j,bi,bj),
154     c & bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj)
155     c end if
156     cmick....................................................
157     else
158 dfer 1.5 omegaC(i,j,k,bi,bj) = 0. _d 0
159 stephd 1.1 endif
160    
161     pHlast(i,j,k,bi,bj) = pHlocal
162    
163     ENDDO
164     ENDDO
165    
166     ENDDO
167     c
168     #endif
169     #endif
170     RETURN
171     END

  ViewVC Help
Powered by ViewVC 1.1.22