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

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

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

revision 1.10 by stephd, Tue Nov 28 21:16:02 2006 UTC revision 1.20 by dfer, Wed Dec 5 16:52:32 2007 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "DIC_OPTIONS.h"  #include "DIC_OPTIONS.h"
5  #include "GCHEM_OPTIONS.h"  #include "GCHEM_OPTIONS.h"
6    
# Line 5  CBOP Line 8  CBOP
8  C !ROUTINE: BIO_EXPORT  C !ROUTINE: BIO_EXPORT
9    
10  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
11        SUBROUTINE BIO_EXPORT( PTR_PO4 ,        SUBROUTINE BIO_EXPORT( PTR_PO4 ,
12  #ifdef ALLOW_FE  #ifdef ALLOW_FE
13       I           PTR_FE,       I           PTR_FE,
14  #endif    #endif
15       I           bioac,       I           bioac,
16       I           bi,bj,imin,imax,jmin,jmax,       I           bi,bj,imin,imax,jmin,jmax,
17       I           myIter,myTime,myThid)       I           myIter,myTime,myThid)
18    
19  c !DESCRIPTION:  c !DESCRIPTION:
20  C  Calculate biological activity and export                  C  Calculate biological activity and export
21    
22  C !USES: ===============================================================  C !USES: ===============================================================
23        IMPLICIT NONE        IMPLICIT NONE
# Line 25  C !USES: =============================== Line 28  C !USES: ===============================
28  #include "GRID.h"  #include "GRID.h"
29  #include "DIC_ABIOTIC.h"  #include "DIC_ABIOTIC.h"
30  #include "DIC_BIOTIC.h"  #include "DIC_BIOTIC.h"
31    #ifdef USE_QSW
32    #include "FFIELDS.h"
33    #endif
34    
35  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
36  C  myThid               :: thread number  C  myThid               :: thread number
# Line 63  CEOP Line 69  CEOP
69    
70    
71  #ifndef READ_PAR  #ifndef READ_PAR
72    #ifndef USE_QSW
73          call insol(myTime,sfac,bj)          call insol(myTime,sfac,bj)
74  #endif  #endif
75    #endif
76          DO j=jmin,jmax          DO j=jmin,jmax
77           DO i=imin,imax           DO i=imin,imax
78  C Fortran-90  C Fortran-90
# Line 75  C FORTRAN-77 with know max of nlev Line 83  C FORTRAN-77 with know max of nlev
83  C$TAF INIT bio_export = static, 10  C$TAF INIT bio_export = static, 10
84  #ifdef READ_PAR  #ifdef READ_PAR
85             lit=PAR(i,j,bi,bj)             lit=PAR(i,j,bi,bj)
86    #elif (defined USE_QSW)
87               lit=-parfrac*Qsw(i,j,bi,bj)*maskC(i,j,1,bi,bj)
88  #else  #else
89             lit=sfac(j)             lit=sfac(j)
90  #endif  #endif
91    
92               IF ( .NOT. QSW_underice ) THEN
93    c if using Qsw but not seaice/thsice or coupled, then
94    c ice fraction needs to be taken into account
95                  lit=lit*(1. _d 0 - FIce(i,j,bi,bj))
96               ENDIF
97    c
98             DO k=1,nlev             DO k=1,nlev
99  C$TAF STORE lit = bio_export  C$TAF STORE lit = bio_export
100               atten=(k0*drF(k)*hFacC(i,j,k,bi,bj)*.5)               atten=(k0*drF(k)*hFacC(i,j,k,bi,bj)*.5 _d 0)
101               if (k.gt.1) atten=atten+(k0*drF(k-1)               if (k.gt.1) atten=atten+(k0*drF(k-1)
102       &                         *hFacC(i,j,k-1,bi,bj)*.5)       &                         *hFacC(i,j,k-1,bi,bj)*.5 _d 0)
103               lit=lit*exp(-atten)*(1.d0-Fice(i,j,bi,bj))               lit=lit*exp(-atten)
104               if (lit.lt.0.d0.or.lit.gt.150) then               IF (lit.LT.0. _d 0.OR.lit.GT.350. _d 0) THEN
105                   print*,'QQ lit', lit                   print*,'QQ lit', lit
106               endif               ENDIF
107    
108  #ifdef ALLOW_FE  #ifdef ALLOW_FE
109  #ifdef AD_SAFE  #ifdef AD_SAFE
110               thx = PTR_PO4(i,j,k)/(PTR_PO4(i,j,k)+KPO4)               thx = PTR_PO4(i,j,k)/(PTR_PO4(i,j,k)+KPO4)
111               thy = PTR_FE(i,j,k)/(PTR_FE(i,j,k)+KFE)               thy = PTR_FE(i,j,k)/(PTR_FE(i,j,k)+KFE)
112               theps = 1.d-6               theps = 1. _d -6
113               nutlimit= ( 1.d0 - tanh((thx-thy)/theps) ) * thx/2 +               nutlimit= ( 1. _d 0 - tanh((thx-thy)/theps) ) * thx/2. _d 0
114       &                 ( 1.d0 + tanh((thx-thy)/theps) ) * thy/2       &                +( 1. _d 0 + tanh((thx-thy)/theps) ) * thy/2. _d 0
115  #else  #else
116               nutlimit=   min(PTR_PO4(i,j,k)/(PTR_PO4(i,j,k)+KPO4),               nutlimit=   min(PTR_PO4(i,j,k)/(PTR_PO4(i,j,k)+KPO4),
117       &                        PTR_FE(i,j,k)/(PTR_FE(i,j,k)+KFE) )       &                        PTR_FE(i,j,k)/(PTR_FE(i,j,k)+KFE) )

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

  ViewVC Help
Powered by ViewVC 1.1.22