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

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

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

revision 1.19 by dfer, Wed Dec 12 01:41:26 2007 UTC revision 1.23 by jmc, Tue Aug 4 18:33:07 2009 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "DIC_OPTIONS.h"  #include "DIC_OPTIONS.h"
 #include "GCHEM_OPTIONS.h"  
5    
6  CBOP  CBOP
7  C !ROUTINE: DIC_BIOTIC_FORCING  C !ROUTINE: DIC_BIOTIC_FORCING
8    
9  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
10        SUBROUTINE DIC_BIOTIC_FORCING( PTR_DIC, PTR_ALK, PTR_PO4,        SUBROUTINE DIC_BIOTIC_FORCING( PTR_DIC, PTR_ALK, PTR_PO4,
11       &                            PTR_DOP,       &                            PTR_DOP,
12  #ifdef ALLOW_O2  #ifdef ALLOW_O2
13       &                            PTR_O2,       &                            PTR_O2,
14  #endif  #endif
15  #ifdef ALLOW_FE  #ifdef ALLOW_FE
16       &                            PTR_FE,       &                            PTR_FE,
# Line 30  C !USES: =============================== Line 29  C !USES: ===============================
29  #include "EEPARAMS.h"  #include "EEPARAMS.h"
30  #include "PARAMS.h"  #include "PARAMS.h"
31  #include "GRID.h"  #include "GRID.h"
32  #include "DIC_BIOTIC.h"  #include "DIC_VARS.h"
 #include "DIC_ABIOTIC.h"  
33    
34  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
35  C  myThid               :: thread number  C  myThid               :: thread number
# Line 70  C                            and virtual Line 68  C                            and virtual
68  C  SURO                   :: tendency of O2 due to air-sea exchange  C  SURO                   :: tendency of O2 due to air-sea exchange
69  C  GPO4                   :: tendency of PO4 due to biological productivity,  C  GPO4                   :: tendency of PO4 due to biological productivity,
70  C                            exchange with DOP pool and reminerization  C                            exchange with DOP pool and reminerization
71  C  CAR                    :: carbonate changes due to biological  C  CAR                    :: carbonate changes due to biological
72  C                             productivity and remineralization  C                             productivity and remineralization
73  C  BIOac                  :: biological productivity  C  BIOac                  :: biological productivity
74  C  RDOP                   :: DOP sink due to remineralization  C  RDOP                   :: DOP sink due to remineralization
75  C  pflux                  :: changes to PO4 due to flux and remineralization  C  pflux                  :: changes to PO4 due to flux and remineralization
76  C  CAR_S                  :: carbonate sink  C  CAR_S                  :: carbonate sink
77  C  cflux                  :: carbonate changes due to flux and remineralization  C  cflux                  :: carbonate changes due to flux and remineralization
78  C  freefe                 :: iron not bound to ligand  C  freefe                 :: iron not bound to ligand
79        _RL  GDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL  GDIC(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
# Line 102  C  freefe                 :: iron not bo Line 100  C  freefe                 :: iron not bo
100         INTEGER I,J,k         INTEGER I,J,k
101         INTEGER nCALCITEstep         INTEGER nCALCITEstep
102  CEOP  CEOP
        jmin=1  
        jmax=sNy  
        imin=1  
        imax=sNx  
103    
104         DO k=1,Nr         DO k=1,Nr
105           DO j=1-OLy,sNy+OLy           DO j=1-OLy,sNy+OLy
# Line 158  c oxygen air-sea interaction Line 152  c oxygen air-sea interaction
152    
153  #ifdef ALLOW_FE  #ifdef ALLOW_FE
154  c find free iron  c find free iron
155         call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,         CALL FE_CHEM(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
156       &                myIter, mythid)       &                myIter, mythid)
157  #endif  #endif
158    
159    
160  c biological activity  c biological activity
161         CALL BIO_EXPORT( PTR_PO4 ,         CALL BIO_EXPORT( PTR_PO4 ,
162  #ifdef ALLOW_FE  #ifdef ALLOW_FE
163       I           PTR_FE,       I           PTR_FE,
164  #endif  #endif
165       I           BIOac,       I           BIOac,
166       I           bi,bj,imin,imax,jmin,jmax,       I           bi,bj,imin,imax,jmin,jmax,
167       I           myIter,myTime,myThid)       I           myIter,myTime,myThid)
# Line 182  C- Carbonate sink Line 176  C- Carbonate sink
176           DO j=jmin,jmax           DO j=jmin,jmax
177            DO i=imin,imax            DO i=imin,imax
178               CAR_S(i,j,k)=BIOac(i,j,k)*R_CP*rain_ratio(i,j,bi,bj)*               CAR_S(i,j,k)=BIOac(i,j,k)*R_CP*rain_ratio(i,j,bi,bj)*
179       &                    (1. _d 0-DOPfraction)       &                    (1. _d 0-DOPfraction)
180            ENDDO            ENDDO
181           ENDDO           ENDDO
182         ENDDO         ENDDO
# Line 289  C update Line 283  C update
283  c find free iron and get rid of insoluble part  c find free iron and get rid of insoluble part
284         call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,         call fe_chem(bi,bj,iMin,iMax,jMin,jMax, PTR_FE, freefe,
285       &                myIter, mythid)       &                myIter, mythid)
286  #endif  #endif
287  #endif  #endif
288    
289    
290  #ifdef ALLOW_TIMEAVE  #ifdef ALLOW_TIMEAVE
291  c save averages  c save averages
292        IF ( taveFreq.GT.0. ) THEN         IF ( taveFreq.GT.0. ) THEN
293        DO k=1,Nr          DO k=1,Nr
294           DO j=jmin,jmax           DO j=jmin,jmax
295            DO i=imin,imax            DO i=imin,imax
296              BIOave(i,j,k,bi,bj)   =BIOave(i,j,k,bi,bj)+              BIOave(i,j,k,bi,bj)   =BIOave(i,j,k,bi,bj)+
# Line 313  c save averages Line 307  c save averages
307       &                             cflux(i,j,k)*deltaTclock       &                             cflux(i,j,k)*deltaTclock
308            ENDDO            ENDDO
309           ENDDO           ENDDO
310        ENDDO          ENDDO
311           DO j=jmin,jmax           DO j=jmin,jmax
312            DO i=imin,imax            DO i=imin,imax
313                SURave(i,j,bi,bj)    =SURave(i,j,bi,bj)+                SURave(i,j,bi,bj)    =SURave(i,j,bi,bj)+
# Line 330  c save averages Line 324  c save averages
324       &                           fluxCO2(i,j,bi,bj)*deltaTclock       &                           fluxCO2(i,j,bi,bj)*deltaTclock
325            ENDDO            ENDDO
326           ENDDO           ENDDO
327        do k=1,Nr           DO k=1,Nr
328         dic_timeave(bi,bj,k)=dic_timeave(bi,bj,k)+deltaTclock            DIC_timeAve(k,bi,bj) = DIC_timeAve(k,bi,bj)+deltaTclock
329        enddo           ENDDO
330        ENDIF         ENDIF
331  #endif /* ALLOW_TIMEAVE*/  #endif /* ALLOW_TIMEAVE*/
332    
333  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

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

  ViewVC Help
Powered by ViewVC 1.1.22