1 |
#include "CPP_OPTIONS.h" |
C $Header$ |
2 |
|
C $Name$ |
3 |
|
|
4 |
|
#include "DIC_OPTIONS.h" |
5 |
#include "PTRACERS_OPTIONS.h" |
#include "PTRACERS_OPTIONS.h" |
6 |
#include "GCHEM_OPTIONS.h" |
#include "GCHEM_OPTIONS.h" |
7 |
|
|
8 |
CStartOfInterFace |
CBOP |
9 |
SUBROUTINE DIC_SURFFORCING( PTR_CO2 , GDC, |
C !ROUTINE: DIC_SURFFORCING |
10 |
|
|
11 |
|
C !INTERFACE: ========================================================== |
12 |
|
SUBROUTINE DIC_SURFFORCING( PTR_CO2 , PTR_ALK, PTR_PO4, GDC, |
13 |
I bi,bj,imin,imax,jmin,jmax, |
I bi,bj,imin,imax,jmin,jmax, |
14 |
I myIter,myTime,myThid) |
I myIter,myTime,myThid) |
15 |
|
|
16 |
C /==========================================================\ |
C !DESCRIPTION: |
17 |
C | SUBROUTINE DIC_SURFFORCING | |
C Calculate the carbon air-sea flux terms |
18 |
C | o Calculate the carbon air-sea flux terms | |
C following external_forcing_dic.F (OCMIP run) from Mick |
|
C | o following external_forcing_dic.F from Mick | |
|
|
C |==========================================================| |
|
|
IMPLICIT NONE |
|
19 |
|
|
20 |
C == GLobal variables == |
C !USES: =============================================================== |
21 |
|
IMPLICIT NONE |
22 |
#include "SIZE.h" |
#include "SIZE.h" |
23 |
#include "DYNVARS.h" |
#include "DYNVARS.h" |
24 |
#include "EEPARAMS.h" |
#include "EEPARAMS.h" |
26 |
#include "GRID.h" |
#include "GRID.h" |
27 |
#include "FFIELDS.h" |
#include "FFIELDS.h" |
28 |
#include "DIC_ABIOTIC.h" |
#include "DIC_ABIOTIC.h" |
|
#ifdef DIC_BIOTIC |
|
|
#include "PTRACERS.h" |
|
|
#endif |
|
29 |
|
|
30 |
C == Routine arguments == |
C !INPUT PARAMETERS: =================================================== |
31 |
|
C myThid :: thread number |
32 |
|
C myIter :: current timestep |
33 |
|
C myTime :: current time |
34 |
|
c PTR_CO2 :: DIC tracer field |
35 |
INTEGER myIter, myThid |
INTEGER myIter, myThid |
36 |
_RL myTime |
_RL myTime |
37 |
_RL PTR_CO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
_RL PTR_CO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
38 |
_RL GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
_RL PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
39 |
|
_RL PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
40 |
INTEGER iMin,iMax,jMin,jMax, bi, bj |
INTEGER iMin,iMax,jMin,jMax, bi, bj |
41 |
|
|
42 |
|
C !OUTPUT PARAMETERS: =================================================== |
43 |
|
c GDC :: tendency due to air-sea exchange |
44 |
|
_RL GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
45 |
|
|
46 |
#ifdef ALLOW_PTRACERS |
#ifdef ALLOW_PTRACERS |
47 |
#ifdef DIC_ABIOTIC |
|
48 |
C == Local variables == |
C !LOCAL VARIABLES: ==================================================== |
49 |
INTEGER I,J, kLev |
INTEGER I,J, kLev, it |
50 |
C Number of iterations for pCO2 solvers... |
C Number of iterations for pCO2 solvers... |
|
INTEGER inewtonmax |
|
|
INTEGER ibrackmax |
|
|
INTEGER donewt |
|
51 |
C Solubility relation coefficients |
C Solubility relation coefficients |
52 |
_RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
_RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
53 |
_RL pCO2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
_RL pCO2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
57 |
_RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
_RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
58 |
_RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
_RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
59 |
_RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
_RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
60 |
_RL FluxCO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
CEOP |
61 |
|
|
62 |
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc |
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc |
63 |
|
|
64 |
kLev=1 |
kLev=1 |
65 |
|
|
66 |
|
c if coupled to atmsopheric model, use the |
67 |
|
c Co2 value passed from the coupler |
68 |
|
#ifndef USE_ATMOSCO2 |
69 |
C PRE-INDUSTRIAL STEADY STATE pCO2 = 278.0 ppmv |
C PRE-INDUSTRIAL STEADY STATE pCO2 = 278.0 ppmv |
70 |
DO j=1-OLy,sNy+OLy |
DO j=1-OLy,sNy+OLy |
71 |
DO i=1-OLx,sNx+OLx |
DO i=1-OLx,sNx+OLx |
72 |
AtmospCO2(i,j,bi,bj)=278.0d-6 |
AtmospCO2(i,j,bi,bj)=278.0d-6 |
73 |
ENDDO |
ENDDO |
74 |
ENDDO |
ENDDO |
75 |
|
#endif |
76 |
|
|
77 |
|
|
78 |
C ================================================================= |
C ================================================================= |
79 |
C determine inorganic carbon chem coefficients |
C determine inorganic carbon chem coefficients |
80 |
DO j=1-OLy,sNy+OLy |
DO j=jmin,jmax |
81 |
DO i=1-OLx,sNx+OLx |
DO i=imin,imax |
82 |
|
|
83 |
#ifdef DIC_BIOTIC |
#ifdef DIC_BIOTIC |
84 |
cQQQQ check ptracer numbers |
cQQQQ check ptracer numbers |
85 |
surfalk(i,j) = PTRACER(i,j,klev,bi,bj,2) |
surfalk(i,j) = PTR_ALK(i,j,klev) |
86 |
& * maskC(i,j,kLev,bi,bj) |
& * maskC(i,j,kLev,bi,bj) |
87 |
surfphos(i,j) = PTRACER(i,j,klev,bi,bj,3) |
surfphos(i,j) = PTR_PO4(i,j,klev) |
88 |
& * maskC(i,j,kLev,bi,bj) |
& * maskC(i,j,kLev,bi,bj) |
89 |
#else |
#else |
90 |
surfalk(i,j) = 2.366595 * salt(i,j,kLev,bi,bj)/gsm_s |
surfalk(i,j) = 2.366595 * salt(i,j,kLev,bi,bj)/gsm_s |
92 |
surfphos(i,j) = 5.1225e-4 * maskC(i,j,kLev,bi,bj) |
surfphos(i,j) = 5.1225e-4 * maskC(i,j,kLev,bi,bj) |
93 |
#endif |
#endif |
94 |
C FOR NON-INTERACTIVE Si |
C FOR NON-INTERACTIVE Si |
95 |
surfsi(i,j) = 7.6838e-3 * maskC(i,j,kLev,bi,bj) |
surfsi(i,j) = SILICA(i,j,bi,bj) * maskC(i,j,kLev,bi,bj) |
96 |
ENDDO |
ENDDO |
97 |
ENDDO |
ENDDO |
98 |
|
|
101 |
I bi,bj,iMin,iMax,jMin,jMax) |
I bi,bj,iMin,iMax,jMin,jMax) |
102 |
C==================================================================== |
C==================================================================== |
103 |
|
|
|
#define PH_APPROX |
|
|
c set number of iterations for [H+] solvers |
|
|
#ifdef PH_APPROX |
|
|
inewtonmax = 1 |
|
|
#else |
|
|
inewtonmax = 10 |
|
|
#endif |
|
|
ibrackmax = 30 |
|
|
C determine pCO2 in surface ocean |
|
|
C set guess of pH for first step here |
|
|
C IF first step THEN use bracket-bisection for first step, |
|
|
C and determine carbon coefficients for safety |
|
|
C ELSE use newton-raphson with previous H+(x,y) as first guess |
|
|
|
|
|
donewt=1 |
|
|
|
|
|
c for first few timesteps |
|
|
IF(myIter .le. (nIter0+inewtonmax) )then |
|
|
donewt=0 |
|
|
DO j=1-OLy,sNy+OLy |
|
|
DO i=1-OLx,sNx+OLx |
|
|
pH(i,j,bi,bj) = 8.0 |
|
|
ENDDO |
|
|
ENDDO |
|
|
#ifdef PH_APPROX |
|
|
print*,'QQ: pCO2 approximation method' |
|
|
c first approxmation |
|
|
DO j=1-OLy,sNy+OLy |
|
|
DO i=1-OLx,sNx+OLx |
|
|
CALL CALC_PCO2_APPROX( |
|
|
I theta(i,j,kLev,bi,bj),salt(i,j,kLev,bi,bj), |
|
|
I PTR_CO2(i,j,kLev), surfphos(i,j), |
|
|
I surfsi(i,j),surfalk(i,j), |
|
|
I ak1(i,j,bi,bj),ak2(i,j,bi,bj), |
|
|
I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj), |
|
|
I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj), |
|
|
I aksi(i,j,bi,bj),akf(i,j,bi,bj),ff(i,j,bi,bj), |
|
|
I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj), |
|
|
U pH(i,j,bi,bj),pCO2(i,j,bi,bj) ) |
|
|
ENDDO |
|
|
ENDDO |
|
|
#else |
|
|
print*,'QQ: pCO2 full method' |
|
|
#endif |
|
|
ENDIF |
|
|
|
|
|
|
|
104 |
c pCO2 solver... |
c pCO2 solver... |
105 |
DO j=1-OLy,sNy+OLy |
C$TAF LOOP = parallel |
106 |
DO i=1-OLx,sNx+OLx |
DO j=jmin,jmax |
107 |
|
C$TAF LOOP = parallel |
108 |
|
DO i=imin,imax |
109 |
|
|
110 |
IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN |
IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN |
|
#ifdef PH_APPROX |
|
111 |
CALL CALC_PCO2_APPROX( |
CALL CALC_PCO2_APPROX( |
112 |
I theta(i,j,kLev,bi,bj),salt(i,j,kLev,bi,bj), |
I theta(i,j,kLev,bi,bj),salt(i,j,kLev,bi,bj), |
113 |
I PTR_CO2(i,j,kLev), surfphos(i,j), |
I PTR_CO2(i,j,kLev), surfphos(i,j), |
118 |
I aksi(i,j,bi,bj),akf(i,j,bi,bj),ff(i,j,bi,bj), |
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), |
I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj), |
120 |
U pH(i,j,bi,bj),pCO2(i,j,bi,bj) ) |
U pH(i,j,bi,bj),pCO2(i,j,bi,bj) ) |
|
#else |
|
|
CALL CALC_PCO2(donewt,inewtonmax,ibrackmax, |
|
|
I theta(i,j,kLev,bi,bj),salt(i,j,kLev,bi,bj), |
|
|
I PTR_CO2(i,j,kLev), surfphos(i,j), |
|
|
I surfsi(i,j),surfalk(i,j), |
|
|
I ak1(i,j,bi,bj),ak2(i,j,bi,bj), |
|
|
I ak1p(i,j,bi,bj),ak2p(i,j,bi,bj),ak3p(i,j,bi,bj), |
|
|
I aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj), |
|
|
I aksi(i,j,bi,bj),akf(i,j,bi,bj),ff(i,j,bi,bj), |
|
|
I bt(i,j,bi,bj),st(i,j,bi,bj),ft(i,j,bi,bj), |
|
|
U pH(i,j,bi,bj),pCO2(i,j,bi,bj) ) |
|
|
#endif |
|
121 |
ELSE |
ELSE |
122 |
pCO2(i,j,bi,bj)=0. _d 0 |
pCO2(i,j,bi,bj)=0. _d 0 |
123 |
END IF |
END IF |
124 |
ENDDO |
ENDDO |
125 |
ENDDO |
ENDDO |
126 |
|
|
127 |
DO j=1-OLy,sNy+OLy |
DO j=jmin,jmax |
128 |
DO i=1-OLx,sNx+OLx |
DO i=imin,imax |
129 |
|
|
130 |
IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN |
IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN |
131 |
C calculate SCHMIDT NO. for CO2 |
C calculate SCHMIDT NO. for CO2 |
136 |
& + sca4 * theta(i,j,kLev,bi,bj)*theta(i,j,kLev,bi,bj) |
& + sca4 * theta(i,j,kLev,bi,bj)*theta(i,j,kLev,bi,bj) |
137 |
& *theta(i,j,kLev,bi,bj) |
& *theta(i,j,kLev,bi,bj) |
138 |
|
|
139 |
|
c |
140 |
|
#ifdef USE_PLOAD |
141 |
|
C Convert anomalous pressure pLoad (in Pa) from atmospheric model |
142 |
|
C to total pressure (in Atm) |
143 |
|
C Note: it is assumed the reference atmospheric pressure is 1Atm=1013mb |
144 |
|
C rather than the actual ref. pressure from Atm. model so that on |
145 |
|
C average AtmosP is about 1 Atm. |
146 |
|
AtmosP(i,j,bi,bj)= 1. _d 0 + pLoad(i,j,bi,bj)/Pa2Atm |
147 |
|
#endif |
148 |
|
|
149 |
C Determine surface flux (FDIC) |
C Determine surface flux (FDIC) |
150 |
C first correct pCO2at for surface atmos pressure |
C first correct pCO2at for surface atmos pressure |
151 |
pCO2sat(i,j) = |
pCO2sat(i,j) = |
152 |
& AtmosP(i,j,bi,bj)*AtmospCO2(i,j,bi,bj) |
& AtmosP(i,j,bi,bj)*AtmospCO2(i,j,bi,bj) |
153 |
c find exchange coefficient |
c find exchange coefficient |
154 |
c account for schmidt number and and varible piston velocity |
c account for schmidt number and and varible piston velocity |
155 |
|
pisvel(i,j,bi,bj) =0.337*wind(i,j,bi,bj)**2/3.6d5 |
156 |
Kwexch(i,j) = |
Kwexch(i,j) = |
157 |
& pisvel(i,j,bi,bj) |
& pisvel(i,j,bi,bj) |
158 |
& / sqrt(SchmidtNoDIC(i,j)/660.0) |
& / sqrt(SchmidtNoDIC(i,j)/660.0) |
159 |
c OR use a constant coeff |
c OR use a constant coeff |
160 |
c Kwexch(i,j) = 5e-5 |
c Kwexch(i,j) = 5e-5 |
161 |
c ice influence |
c ice influence |
162 |
cQQ Kwexch(i,j) =(1.d0-Fice(i,j,bi,bj))*Kwexch(i,j) |
Kwexch(i,j) =(1.d0-Fice(i,j,bi,bj))*Kwexch(i,j) |
163 |
|
|
164 |
|
|
165 |
C Calculate flux in terms of DIC units using K0, solubility |
C Calculate flux in terms of DIC units using K0, solubility |
166 |
C Flux = Vp * ([CO2sat] - [CO2]) |
C Flux = Vp * ([CO2sat] - [CO2]) |
167 |
C CO2sat = K0*pCO2atmos*P/P0 |
C CO2sat = K0*pCO2atmos*P/P0 |
168 |
C Converting pCO2 to [CO2] using ff, as in CALC_PCO2 |
C Converting pCO2 to [CO2] using ff, as in CALC_PCO2 |
169 |
FluxCO2(i,j) = |
FluxCO2(i,j,bi,bj) = |
170 |
& maskC(i,j,kLev,bi,bj)*Kwexch(i,j)*( |
& maskC(i,j,kLev,bi,bj)*Kwexch(i,j)*( |
171 |
& ak0(i,j,bi,bj)*pCO2sat(i,j) - |
& ak0(i,j,bi,bj)*pCO2sat(i,j) - |
172 |
& ff(i,j,bi,bj)*pCO2(i,j,bi,bj) |
& ff(i,j,bi,bj)*pCO2(i,j,bi,bj) |
173 |
& ) |
& ) |
174 |
ELSE |
ELSE |
175 |
FluxCO2(i,j) = 0. |
FluxCO2(i,j,bi,bj) = 0. |
176 |
ENDIF |
ENDIF |
177 |
C convert flux (mol kg-1 m s-1) to (mol m-2 s-1) |
C convert flux (mol kg-1 m s-1) to (mol m-2 s-1) |
178 |
FluxCO2(i,j) = FluxCO2(i,j)/permil |
FluxCO2(i,j,bi,bj) = FluxCO2(i,j,bi,bj)/permil |
179 |
|
|
180 |
IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN |
IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN |
181 |
c calculate virtual flux |
c calculate virtual flux |
185 |
C in salinity. Thus, also increase in other surface tracers |
C in salinity. Thus, also increase in other surface tracers |
186 |
C (i.e. positive virtual flux into surface layer) |
C (i.e. positive virtual flux into surface layer) |
187 |
C ...so here, VirtualFLux = dC/dt! |
C ...so here, VirtualFLux = dC/dt! |
188 |
VirtualFlux(i,j)=gsm_DIC*surfaceTendencyS(i,j,bi,bj)/gsm_s |
VirtualFlux(i,j)=gsm_DIC*surfaceForcingS(i,j,bi,bj)/gsm_s |
189 |
c OR |
c OR |
190 |
c let virtual flux be zero |
c let virtual flux be zero |
191 |
c VirtualFlux(i,j)=0.d0 |
c VirtualFlux(i,j)=0.d0 |
197 |
ENDDO |
ENDDO |
198 |
|
|
199 |
C update tendency |
C update tendency |
200 |
DO j=1-OLy,sNy+OLy |
DO j=jmin,jmax |
201 |
DO i=1-OLx,sNx+OLx |
DO i=imin,imax |
202 |
GDC(i,j)= maskC(i,j,kLev,bi,bj)*( |
GDC(i,j)= maskC(i,j,kLev,bi,bj)*recip_drF(kLev)* |
203 |
& FluxCO2(i,j)*recip_drF(kLev) |
& recip_hFacC(i,j,kLev,bi,bj)*( |
204 |
& + VirtualFlux(i,j) |
& FluxCO2(i,j,bi,bj) + VirtualFlux(i,j) |
205 |
& ) |
& ) |
206 |
ENDDO |
ENDDO |
207 |
ENDDO |
ENDDO |
208 |
|
|
209 |
#endif |
#endif |
|
#endif |
|
210 |
RETURN |
RETURN |
211 |
END |
END |