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

Diff of /MITgcm/pkg/dic/dic_surfforcing.F

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

revision 1.4 by edhill, Thu Oct 9 04:19:19 2003 UTC revision 1.23 by jmc, Sun Apr 11 22:03:53 2010 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "DIC_OPTIONS.h"  #include "DIC_OPTIONS.h"
5  #include "PTRACERS_OPTIONS.h"  #include "PTRACERS_OPTIONS.h"
 #include "GCHEM_OPTIONS.h"  
6    
7  CStartOfInterFace  CBOP
8        SUBROUTINE DIC_SURFFORCING( PTR_CO2 , GDC,  C !ROUTINE: DIC_SURFFORCING
9    
10    C !INTERFACE: ==========================================================
11          SUBROUTINE DIC_SURFFORCING( PTR_CO2 , PTR_ALK, PTR_PO4, GDC,
12       I           bi,bj,imin,imax,jmin,jmax,       I           bi,bj,imin,imax,jmin,jmax,
13       I           myIter,myTime,myThid)       I           myIter,myTime,myThid)
14    
15  C     /==========================================================\  C !DESCRIPTION:
16  C     | SUBROUTINE DIC_SURFFORCING                               |  C  Calculate the carbon air-sea flux terms              
17  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  
18    
19  C     == GLobal variables ==  C !USES: ===============================================================
20          IMPLICIT NONE
21  #include "SIZE.h"  #include "SIZE.h"
22  #include "DYNVARS.h"  #include "DYNVARS.h"
23  #include "EEPARAMS.h"  #include "EEPARAMS.h"
24  #include "PARAMS.h"  #include "PARAMS.h"
25  #include "GRID.h"  #include "GRID.h"
26  #include "FFIELDS.h"  #include "FFIELDS.h"
27  #include "DIC_ABIOTIC.h"  #include "DIC_VARS.h"
 #ifdef DIC_BIOTIC  
 #include "PTRACERS.h"  
 #endif  
28    
29  C     == Routine arguments ==  C !INPUT PARAMETERS: ===================================================
30    C  myThid               :: thread number
31    C  myIter               :: current timestep
32    C  myTime               :: current time
33    c  PTR_CO2              :: DIC tracer field
34        INTEGER myIter, myThid        INTEGER myIter, myThid
35        _RL myTime        _RL myTime
36        _RL  PTR_CO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL  PTR_CO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
37        _RL  GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  PTR_ALK(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
38          _RL  PTR_PO4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
39        INTEGER iMin,iMax,jMin,jMax, bi, bj        INTEGER iMin,iMax,jMin,jMax, bi, bj
40    
41    C !OUTPUT PARAMETERS: ===================================================
42    c GDC                   :: tendency due to air-sea exchange
43          _RL  GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44    
45  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
46  C     == Local variables ==  
47         INTEGER I,J, kLev, it  C !LOCAL VARIABLES: ====================================================
48           INTEGER i,j, kLev
49  C Number of iterations for pCO2 solvers...  C Number of iterations for pCO2 solvers...
50  C Solubility relation coefficients  C Solubility relation coefficients
51        _RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52        _RL pCO2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL pCO2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53        _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL Kwexch(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54          _RL pisvel(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55  C local variables for carbon chem  C local variables for carbon chem
56        _RL surfalk(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL surfalk(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    #ifdef ALLOW_OLD_VIRTUALFLUX
60        _RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61    #endif
62    CEOP
63    
64  cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc  cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
65    
66        kLev=1        kLev=1
67    
68  C PRE-INDUSTRIAL STEADY STATE pCO2 = 278.0 ppmv  cc if coupled to atmsopheric model, use the
69         DO j=1-OLy,sNy+OLy  cc Co2 value passed from the coupler
70          DO i=1-OLx,sNx+OLx  c#ifndef USE_ATMOSCO2
71             AtmospCO2(i,j,bi,bj)=278.0d-6  cC PRE-INDUSTRIAL STEADY STATE pCO2 = 278.0 ppmv
72          ENDDO  c       DO j=1-OLy,sNy+OLy
73         ENDDO  c        DO i=1-OLx,sNx+OLx
74    c           AtmospCO2(i,j,bi,bj)=278.0 _d -6
75    c        ENDDO
76    c       ENDDO
77    c#endif
78    
79    
80  C =================================================================  C =================================================================
81  C determine inorganic carbon chem coefficients  C determine inorganic carbon chem coefficients
82          DO j=1-OLy,sNy+OLy          DO j=jmin,jmax
83           DO i=1-OLx,sNx+OLx           DO i=imin,imax
84    
85  #ifdef DIC_BIOTIC  #ifdef DIC_BIOTIC
86  cQQQQ check ptracer numbers  cQQQQ check ptracer numbers
87               surfalk(i,j) = PTRACER(i,j,klev,bi,bj,2)               surfalk(i,j) = PTR_ALK(i,j,klev)
88       &                          * maskC(i,j,kLev,bi,bj)       &                          * maskC(i,j,kLev,bi,bj)
89               surfphos(i,j)  = PTRACER(i,j,klev,bi,bj,3)               surfphos(i,j)  = PTR_PO4(i,j,klev)
90       &                          * maskC(i,j,kLev,bi,bj)       &                          * maskC(i,j,kLev,bi,bj)
91  #else  #else
92               surfalk(i,j) = 2.366595 * salt(i,j,kLev,bi,bj)/gsm_s               surfalk(i,j) = 2.366595 _d 0 * salt(i,j,kLev,bi,bj)/gsm_s
93       &                          * maskC(i,j,kLev,bi,bj)       &                          * maskC(i,j,kLev,bi,bj)
94               surfphos(i,j)  = 5.1225e-4 * maskC(i,j,kLev,bi,bj)               surfphos(i,j)  = 5.1225 _d -4 * maskC(i,j,kLev,bi,bj)
95  #endif  #endif
96  C FOR NON-INTERACTIVE Si  C FOR NON-INTERACTIVE Si
97               surfsi(i,j)   = SILICA(i,j,bi,bj) * maskC(i,j,kLev,bi,bj)               surfsi(i,j)   = SILICA(i,j,bi,bj) * maskC(i,j,kLev,bi,bj)
# Line 82  C FOR NON-INTERACTIVE Si Line 100  C FOR NON-INTERACTIVE Si
100    
101           CALL CARBON_COEFFS(           CALL CARBON_COEFFS(
102       I                       theta,salt,       I                       theta,salt,
103       I                       bi,bj,iMin,iMax,jMin,jMax)       I                       bi,bj,iMin,iMax,jMin,jMax,myThid)
104  C====================================================================  C====================================================================
105    
106           DO j=jmin,jmax
107            DO i=imin,imax
108    C Compute AtmosP and Kwexch_Pre which are re-used for flux of O2
109    
110    #ifdef USE_PLOAD
111    C Convert anomalous pressure pLoad (in Pa) from atmospheric model
112    C to total pressure (in Atm)
113    C Note: it is assumed the reference atmospheric pressure is 1Atm=1013mb
114    C       rather than the actual ref. pressure from Atm. model so that on
115    C       average AtmosP is about 1 Atm.
116                    AtmosP(i,j,bi,bj)= 1. _d 0 + pLoad(i,j,bi,bj)/Pa2Atm
117    #endif
118    
119    C Pre-compute part of exchange coefficient: pisvel*(1-fice)
120    C Schmidt number is accounted for later
121                  pisvel(i,j)=0.337 _d 0 *wind(i,j,bi,bj)**2/3.6 _d 5
122                  Kwexch_Pre(i,j,bi,bj) = pisvel(i,j)
123         &                              * (1. _d 0 - FIce(i,j,bi,bj))
124    
125            ENDDO
126           ENDDO
127    
128  c pCO2 solver...  c pCO2 solver...
129  C$TAF LOOP = parallel  C$TAF LOOP = parallel
130         DO j=1-OLy,sNy+OLy         DO j=jmin,jmax
131  C$TAF LOOP = parallel  C$TAF LOOP = parallel
132          DO i=1-OLx,sNx+OLx          DO i=imin,imax
133    
134            IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN            IF ( maskC(i,j,kLev,bi,bj).NE.0. _d 0 ) THEN
135              CALL CALC_PCO2_APPROX(              CALL CALC_PCO2_APPROX(
136       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),
137       I        PTR_CO2(i,j,kLev), surfphos(i,j),       I        PTR_CO2(i,j,kLev), surfphos(i,j),
# Line 101  C$TAF LOOP = parallel Line 141  C$TAF LOOP = parallel
141       I        aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),       I        aks(i,j,bi,bj),akb(i,j,bi,bj),akw(i,j,bi,bj),
142       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),
143       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),
144       U        pH(i,j,bi,bj),pCO2(i,j,bi,bj) )       U        pH(i,j,bi,bj),pCO2(i,j,bi,bj),
145         I        myThid )
146            ELSE            ELSE
147               pCO2(i,j,bi,bj)=0. _d 0              pCO2(i,j,bi,bj)=0. _d 0
148            END IF            ENDIF
149          ENDDO          ENDDO
150         ENDDO         ENDDO
151    
152         DO j=1-OLy,sNy+OLy         DO j=jmin,jmax
153          DO i=1-OLx,sNx+OLx          DO i=imin,imax
154    
155              IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN            IF ( maskC(i,j,kLev,bi,bj).NE.0. _d 0 ) THEN
156  C calculate SCHMIDT NO. for CO2  C calculate SCHMIDT NO. for CO2
157                SchmidtNoDIC(i,j) =                SchmidtNoDIC(i,j) =
158       &            sca1       &            sca1
# Line 124  C Determine surface flux (FDIC) Line 165  C Determine surface flux (FDIC)
165  C first correct pCO2at for surface atmos pressure  C first correct pCO2at for surface atmos pressure
166                pCO2sat(i,j) =                pCO2sat(i,j) =
167       &          AtmosP(i,j,bi,bj)*AtmospCO2(i,j,bi,bj)       &          AtmosP(i,j,bi,bj)*AtmospCO2(i,j,bi,bj)
 c find exchange coefficient  
 c  account for schmidt number and and varible piston velocity  
               Kwexch(i,j) =  
      &             pisvel(i,j,bi,bj)  
      &             / sqrt(SchmidtNoDIC(i,j)/660.0)  
 c OR use a constant  coeff  
 c             Kwexch(i,j) = 5e-5  
 c ice influence  
 cQQ           Kwexch(i,j)  =(1.d0-Fice(i,j,bi,bj))*Kwexch(i,j)  
168    
169    C then account for Schmidt number
170                  Kwexch(i,j) = Kwexch_Pre(i,j,bi,bj)
171         &                    / sqrt(SchmidtNoDIC(i,j)/660.0 _d 0)
172    
173  C Calculate flux in terms of DIC units using K0, solubility  C Calculate flux in terms of DIC units using K0, solubility
174  C Flux = Vp * ([CO2sat] - [CO2])  C Flux = Vp * ([CO2sat] - [CO2])
175  C CO2sat = K0*pCO2atmos*P/P0  C CO2sat = K0*pCO2atmos*P/P0
176  C Converting pCO2 to [CO2] using ff, as in CALC_PCO2  C Converting pCO2 to [CO2] using ff, as in CALC_PCO2
177                FluxCO2(i,j,bi,bj) =                FluxCO2(i,j,bi,bj) =
178       &         maskC(i,j,kLev,bi,bj)*Kwexch(i,j)*(       &         Kwexch(i,j)*(
179       &         ak0(i,j,bi,bj)*pCO2sat(i,j) -       &         ak0(i,j,bi,bj)*pCO2sat(i,j) -
180       &         ff(i,j,bi,bj)*pCO2(i,j,bi,bj)       &         ff(i,j,bi,bj)*pCO2(i,j,bi,bj)
181       &         )       &         )
182              ELSE            ELSE
183                 FluxCO2(i,j,bi,bj) = 0.                FluxCO2(i,j,bi,bj) = 0. _d 0
184              ENDIF            ENDIF
185  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)
186              FluxCO2(i,j,bi,bj) = FluxCO2(i,j,bi,bj)/permil              FluxCO2(i,j,bi,bj) = FluxCO2(i,j,bi,bj)/permil
187    
188              IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN  #ifdef ALLOW_OLD_VIRTUALFLUX
189                IF (maskC(i,j,kLev,bi,bj).NE.0. _d 0) THEN
190  c calculate virtual flux  c calculate virtual flux
191  c EminusPforV = dS/dt*(1/Sglob)  c EminusPforV = dS/dt*(1/Sglob)
192  C NOTE: Be very careful with signs here!  C NOTE: Be very careful with signs here!
# Line 158  C Positive EminusPforV => loss of water Line 194  C Positive EminusPforV => loss of water
194  C in salinity. Thus, also increase in other surface tracers  C in salinity. Thus, also increase in other surface tracers
195  C (i.e. positive virtual flux into surface layer)  C (i.e. positive virtual flux into surface layer)
196  C ...so here, VirtualFLux = dC/dt!  C ...so here, VirtualFLux = dC/dt!
197                VirtualFlux(i,j)=gsm_DIC*surfaceTendencyS(i,j,bi,bj)/gsm_s                VirtualFlux(i,j)=gsm_DIC*surfaceForcingS(i,j,bi,bj)/gsm_s
198  c OR  c OR
199  c let virtual flux be zero  c let virtual flux be zero
200  c              VirtualFlux(i,j)=0.d0  c              VirtualFlux(i,j)=0.d0
# Line 166  c Line 202  c
202              ELSE              ELSE
203                VirtualFlux(i,j)=0. _d 0                VirtualFlux(i,j)=0. _d 0
204              ENDIF              ENDIF
205    #endif /* ALLOW_OLD_VIRTUALFLUX */
206            ENDDO            ENDDO
207           ENDDO           ENDDO
208    
209  C update tendency        C update tendency      
210           DO j=1-OLy,sNy+OLy           DO j=jmin,jmax
211            DO i=1-OLx,sNx+OLx            DO i=imin,imax
212             GDC(i,j)= maskC(i,j,kLev,bi,bj)*(             GDC(i,j)= recip_drF(kLev)*recip_hFacC(i,j,kLev,bi,bj)
213       &                    FluxCO2(i,j,bi,bj)*recip_drF(kLev)       &              *(FluxCO2(i,j,bi,bj)
214       &                    + VirtualFlux(i,j)  #ifdef ALLOW_OLD_VIRTUALFLUX
215       &                                              )       &              + VirtualFlux(i,j)
216    #endif
217         &               )
218            ENDDO            ENDDO
219           ENDDO           ENDDO
220    

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.23

  ViewVC Help
Powered by ViewVC 1.1.22