/[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.2 - (hide annotations) (download)
Fri Dec 16 21:07:53 2005 UTC (18 years, 4 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.1: +2 -2 lines
o dic code now does no calculations on the overlap regions

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

  ViewVC Help
Powered by ViewVC 1.1.22