/[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.2 by stephd, Wed Jul 9 19:59:18 2003 UTC revision 1.5 by stephd, Thu Feb 12 16:11:46 2004 UTC
# Line 1  Line 1 
1  #include "CPP_OPTIONS.h"  #include "DIC_OPTIONS.h"
2  #include "PTRACERS_OPTIONS.h"  #include "PTRACERS_OPTIONS.h"
3  #include "GCHEM_OPTIONS.h"  #include "GCHEM_OPTIONS.h"
4    
5  CStartOfInterFace  CBOP
6    C !ROUTINE: DIC_SURFFORCING
7    
8    C !INTERFACE: ==========================================================
9        SUBROUTINE DIC_SURFFORCING( PTR_CO2 , GDC,        SUBROUTINE DIC_SURFFORCING( PTR_CO2 , GDC,
10       I           bi,bj,imin,imax,jmin,jmax,       I           bi,bj,imin,imax,jmin,jmax,
11       I           myIter,myTime,myThid)       I           myIter,myTime,myThid)
12    
13  C     /==========================================================\  C !DESCRIPTION:
14  C     | SUBROUTINE DIC_SURFFORCING                               |  C  Calculate the carbon air-sea flux terms              
15  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  
16    
17  C     == GLobal variables ==  C !USES: ===============================================================
18          IMPLICIT NONE
19  #include "SIZE.h"  #include "SIZE.h"
20  #include "DYNVARS.h"  #include "DYNVARS.h"
21  #include "EEPARAMS.h"  #include "EEPARAMS.h"
# Line 26  C     == GLobal variables == Line 27  C     == GLobal variables ==
27  #include "PTRACERS.h"  #include "PTRACERS.h"
28  #endif  #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)
       _RL  GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
38        INTEGER iMin,iMax,jMin,jMax, bi, bj        INTEGER iMin,iMax,jMin,jMax, bi, bj
39    
40    C !OUTPUT PARAMETERS: ===================================================
41    c GDC                   :: tendency term due to air-sea exchange
42          _RL  GDC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43    
44  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
45  #ifdef DIC_ABIOTIC  
46  C     == Local variables ==  C !LOCAL VARIABLES: ====================================================
47         INTEGER I,J, kLev, it         INTEGER I,J, kLev, it
48  C Number of iterations for pCO2 solvers...  C Number of iterations for pCO2 solvers...
       INTEGER inewtonmax  
       INTEGER ibrackmax  
       INTEGER donewt  
49  C Solubility relation coefficients  C Solubility relation coefficients
50        _RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL SchmidtNoDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51        _RL pCO2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL pCO2sat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 50  C local variables for carbon chem Line 55  C local variables for carbon chem
55        _RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL surfphos(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56        _RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL surfsi(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57        _RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL VirtualFlux(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58    CEOP
59    
60  cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc  cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
61    
# Line 80  cQQQQ check ptracer numbers Line 86  cQQQQ check ptracer numbers
86               surfphos(i,j)  = 5.1225e-4 * maskC(i,j,kLev,bi,bj)               surfphos(i,j)  = 5.1225e-4 * maskC(i,j,kLev,bi,bj)
87  #endif  #endif
88  C FOR NON-INTERACTIVE Si  C FOR NON-INTERACTIVE Si
89               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)
90            ENDDO            ENDDO
91           ENDDO           ENDDO
92    
# Line 89  C FOR NON-INTERACTIVE Si Line 95  C FOR NON-INTERACTIVE Si
95       I                       bi,bj,iMin,iMax,jMin,jMax)       I                       bi,bj,iMin,iMax,jMin,jMax)
96  C====================================================================  C====================================================================
97    
 #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  
          do it=1,10  
           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  
        ENDDO  
 #else  
           print*,'QQ: pCO2 full method'  
 #endif  
        ENDIF  
   
   
98  c pCO2 solver...  c pCO2 solver...
99    C$TAF LOOP = parallel
100         DO j=1-OLy,sNy+OLy         DO j=1-OLy,sNy+OLy
101    C$TAF LOOP = parallel
102          DO i=1-OLx,sNx+OLx          DO i=1-OLx,sNx+OLx
103    
104            IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN            IF(maskC(i,j,kLev,bi,bj) .NE. 0.)THEN
 #ifdef PH_APPROX  
105              CALL CALC_PCO2_APPROX(              CALL CALC_PCO2_APPROX(
106       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),
107       I        PTR_CO2(i,j,kLev), surfphos(i,j),       I        PTR_CO2(i,j,kLev), surfphos(i,j),
# Line 154  c pCO2 solver... Line 112  c pCO2 solver...
112       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),
113       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),
114       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  
115            ELSE            ELSE
116               pCO2(i,j,bi,bj)=0. _d 0               pCO2(i,j,bi,bj)=0. _d 0
117            END IF            END IF
# Line 244  C update tendency Line 190  C update tendency
190           ENDDO           ENDDO
191    
192  #endif  #endif
 #endif  
193          RETURN          RETURN
194          END          END

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22