/[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.3 by stephd, Mon Oct 6 20:11:10 2003 UTC revision 1.10 by stephd, Fri Dec 16 21:07:53 2005 UTC
# Line 1  Line 1 
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    C !ROUTINE: DIC_SURFFORCING
10    
11    C !INTERFACE: ==========================================================
12        SUBROUTINE DIC_SURFFORCING( PTR_CO2 , GDC,        SUBROUTINE DIC_SURFFORCING( PTR_CO2 , 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"
# Line 23  C     == GLobal variables == Line 27  C     == GLobal variables ==
27  #include "FFIELDS.h"  #include "FFIELDS.h"
28  #include "DIC_ABIOTIC.h"  #include "DIC_ABIOTIC.h"
29  #ifdef DIC_BIOTIC  #ifdef DIC_BIOTIC
30    #include "PTRACERS_SIZE.h"
31  #include "PTRACERS.h"  #include "PTRACERS.h"
32  #endif  #endif
33    
34  C     == Routine arguments ==  C !INPUT PARAMETERS: ===================================================
35    C  myThid               :: thread number
36    C  myIter               :: current timestep
37    C  myTime               :: current time
38    c  PTR_CO2              :: DIC tracer field
39        INTEGER myIter, myThid        INTEGER myIter, myThid
40        _RL myTime        _RL myTime
41        _RL  PTR_CO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL  PTR_CO2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
       _RL  GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
42        INTEGER iMin,iMax,jMin,jMax, bi, bj        INTEGER iMin,iMax,jMin,jMax, bi, bj
43    
44    C !OUTPUT PARAMETERS: ===================================================
45    c GDC                   :: tendency due to air-sea exchange
46          _RL  GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47    
48  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
49  C     == Local variables ==  
50    C !LOCAL VARIABLES: ====================================================
51         INTEGER I,J, kLev, it         INTEGER I,J, kLev, it
52  C Number of iterations for pCO2 solvers...  C Number of iterations for pCO2 solvers...
53  C Solubility relation coefficients  C Solubility relation coefficients
# Line 46  C local variables for carbon chem Line 59  C local variables for carbon chem
59        _RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60        _RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61        _RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62    CEOP
63    
64  cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc  cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
65    
# Line 61  C PRE-INDUSTRIAL STEADY STATE pCO2 = 278 Line 75  C PRE-INDUSTRIAL STEADY STATE pCO2 = 278
75    
76  C =================================================================  C =================================================================
77  C determine inorganic carbon chem coefficients  C determine inorganic carbon chem coefficients
78          DO j=1-OLy,sNy+OLy          DO j=jmin,jmax
79           DO i=1-OLx,sNx+OLx           DO i=imin,imax
80    
81  #ifdef DIC_BIOTIC  #ifdef DIC_BIOTIC
82  cQQQQ check ptracer numbers  cQQQQ check ptracer numbers
# Line 87  C======================================= Line 101  C=======================================
101    
102  c pCO2 solver...  c pCO2 solver...
103  C$TAF LOOP = parallel  C$TAF LOOP = parallel
104         DO j=1-OLy,sNy+OLy         DO j=jmin,jmax
105  C$TAF LOOP = parallel  C$TAF LOOP = parallel
106          DO i=1-OLx,sNx+OLx          DO i=imin,imax
107    
108            IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN            IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN
109              CALL CALC_PCO2_APPROX(              CALL CALC_PCO2_APPROX(
# Line 108  C$TAF LOOP = parallel Line 122  C$TAF LOOP = parallel
122          ENDDO          ENDDO
123         ENDDO         ENDDO
124    
125         DO j=1-OLy,sNy+OLy         DO j=jmin,jmax
126          DO i=1-OLx,sNx+OLx          DO i=imin,imax
127    
128              IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN              IF (maskC(i,j,kLev,bi,bj).NE.0.) THEN
129  C calculate SCHMIDT NO. for CO2  C calculate SCHMIDT NO. for CO2
# Line 132  c  account for schmidt number and and va Line 146  c  account for schmidt number and and va
146  c OR use a constant  coeff  c OR use a constant  coeff
147  c             Kwexch(i,j) = 5e-5  c             Kwexch(i,j) = 5e-5
148  c ice influence  c ice influence
149  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)
150    
151    
152  C Calculate flux in terms of DIC units using K0, solubility  C Calculate flux in terms of DIC units using K0, solubility
# Line 158  C Positive EminusPforV => loss of water Line 172  C Positive EminusPforV => loss of water
172  C in salinity. Thus, also increase in other surface tracers  C in salinity. Thus, also increase in other surface tracers
173  C (i.e. positive virtual flux into surface layer)  C (i.e. positive virtual flux into surface layer)
174  C ...so here, VirtualFLux = dC/dt!  C ...so here, VirtualFLux = dC/dt!
175                VirtualFlux(i,j)=gsm_DIC*surfaceTendencyS(i,j,bi,bj)/gsm_s                VirtualFlux(i,j)=gsm_DIC*surfaceForcingS(i,j,bi,bj)/gsm_s
176  c OR  c OR
177  c let virtual flux be zero  c let virtual flux be zero
178  c              VirtualFlux(i,j)=0.d0  c              VirtualFlux(i,j)=0.d0
# Line 170  c Line 184  c
184           ENDDO           ENDDO
185    
186  C update tendency        C update tendency      
187           DO j=1-OLy,sNy+OLy           DO j=jmin,jmax
188            DO i=1-OLx,sNx+OLx            DO i=imin,imax
189             GDC(i,j)= maskC(i,j,kLev,bi,bj)*(             GDC(i,j)= maskC(i,j,kLev,bi,bj)*recip_drF(kLev)*
190       &                    FluxCO2(i,j,bi,bj)*recip_drF(kLev)       &                     recip_hFacC(i,j,kLev,bi,bj)*(
191       &                    + VirtualFlux(i,j)       &                    FluxCO2(i,j,bi,bj) + VirtualFlux(i,j)
192       &                                              )       &                                              )
193            ENDDO            ENDDO
194           ENDDO           ENDDO

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22