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

Annotation of /MITgcm/pkg/dic/car_flux_omega_top.F

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


Revision 1.4 - (hide annotations) (download)
Tue Oct 9 00:01:42 2007 UTC (16 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59i
Changes since 1.3: +3 -0 lines
add missing cvs $Header:$ or $Name:$

1 jmc 1.4 C $Header: $
2     C $Name: $
3    
4 stephd 1.1 #include "DIC_OPTIONS.h"
5     #include "GCHEM_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: CAR_FLUX
9    
10     C !INTERFACE: ==========================================================
11     SUBROUTINE CAR_FLUX_OMEGA_TOP( bioac, cflux,
12     I bi,bj,imin,imax,jmin,jmax,
13     I myIter,myTime,myThid)
14    
15     C !DESCRIPTION:
16     C Calculate carbonate fluxes
17     C HERE ONLY HAVE DISSOLUTION WHEN OMEGA < 1.0
18     C Karsten Friis and Mick Follows Sep 2004
19    
20     C !USES: ===============================================================
21     IMPLICIT NONE
22     #include "SIZE.h"
23     #include "DYNVARS.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "GRID.h"
27     #include "DIC_BIOTIC.h"
28    
29     C !INPUT PARAMETERS: ===================================================
30     C myThid :: thread number
31     C myIter :: current timestep
32     C myTime :: current time
33     C bioac :: biological productivity
34     INTEGER myIter
35     _RL myTime
36     INTEGER myThid
37     _RL bioac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
38     INTEGER imin, imax, jmin, jmax, bi, bj
39    
40     C !OUTPUT PARAMETERS: ===================================================
41     C cflux :: carbonate flux
42     _RL cflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
43    
44     #ifdef ALLOW_PTRACERS
45     #ifdef DIC_BIOTIC
46    
47     C !LOCAL VARIABLES: ====================================================
48     C i,j,k :: loop indices
49     c ko :: loop-within-loop index
50     c caexport :: flux of carbonate from base each "productive"
51     c layer
52     c depth_u, depth_l :: depths of upper and lower interfaces
53     c flux_u, flux_l :: flux through upper and lower interfaces
54     _RL caexport(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55     INTEGER I,J,k, ko
56     _RL flux_u, flux_l
57     c variables for calcium carbonate dissolution
58     _RL KierRate
59     _RL DissolutionRate
60     _RL WsinkPIC
61     INTEGER iflx
62     _RL dumrate
63    
64     c diagnostics
65     c _RL exp_tot
66     c _RL flx_tot
67     c integer knum
68     c _RL omeg_bot
69     c _RL tmp
70    
71    
72     CEOP
73    
74     c flag to either remineralize in bottom or top layer if flux
75     c reaches bottom layer 0=bottom, 1=top
76     iflx=1
77     c set some nominal particulate sinking rate
78     c try 100m/day
79     WsinkPIC = 100/86400.0
80     c calculate carbonate flux from base of each nlev
81 stephd 1.3 DO j=jmin,jmax
82     DO i=imin,imax
83 stephd 1.1 c exp_tot=0
84     do k=1,nR
85     cflux(i,j,k)=0.d0
86     enddo
87     DO k=1,nLev
88     if (hFacC(i,j,k,bi,bj).gt.0.d0) then
89     caexport(i,j)= R_cp*rain_ratio(i,j,bi,bj)*bioac(i,j,k)*
90     & (1.0-DOPfraction)*drF(k)*hFacC(i,j,k,bi,bj)
91     c exp_tot=exp_tot+caexport(i,j)
92     c calculate flux to each layer from base of k
93     Do ko=k+1,Nr
94     if (hFacC(i,j,ko,bi,bj).gt.0.d0) then
95     if (ko .eq. k+1) then
96     flux_u = caexport(i,j)
97     else
98     flux_u = flux_l
99     endif
100    
101    
102    
103     C flux through lower face of cell
104     if (omegaC(i,j,ko,bi,bj) .gt. 1.0) then
105     flux_l = flux_u
106    
107     c if at bottom, remineralize remaining flux
108     if (ko.eq.Nr.or.hFacC(i,j,ko+1,bi,bj).eq.0.d0) then
109     if (iflx.eq.1) then
110     c ... at surface
111     cflux(i,j,1)=cflux(i,j,1)+
112     & ( (flux_l)/(drF(1)*hFacC(i,j,1,bi,bj)) )
113     else
114    
115     c ... at bottom
116     flux_l=0.d0
117     endif
118     endif
119     else
120     c if dissolution, then use rate from Kier (1980) Geochem. Cosmochem. Acta
121     c Kiers dissolution rate in % per day
122     KierRate = 7.177* ((1.0-omegaC(i,j,ko,bi,bj))**4.54)
123     c convert to per s
124     c Karsten finds Kier value not in 0/0 after all... therefore drop 100 factor
125     c DissolutionRate = KierRate/(100.0*86400.0)
126     DissolutionRate = KierRate/(86400.0)
127     c flux_l = flux_u*(1.0-DissolutionRate*drF(k)/WsinkPIC)
128     c Karstens version
129     c - gives NaNs (because using kierrate, not dissolution rate)???
130     c flux_l = flux_u*(1.0-KierRate)**(drF(k)/WsinkPIC)
131     c MICKS NEW VERSION... based on vertical sinking/remin balance
132 stephd 1.2 dumrate = -1.0d0*DissolutionRate*drF(ko)*
133     & hFacC(i,j,ko,bi,bj)/WsinkPIC
134 stephd 1.1 flux_l = flux_u*exp(dumrate)
135     c TEST ............................
136     c if(i .eq. 76 .and. j .eq. 36)then
137     c write(6,*)'k,flux_l/flux_u',ko,(flux_l/flux_u)
138     c write(6,*)'K, KierRate, drF(k), drF(ko), WsinkPIC,OmegaC'
139     c write(6,*)ko,KierRate,drF(k),drF(ko),WsinkPIC,
140     c & omegaC(i,j,ko,bi,bj)
141     c endif
142     c TEST ............................
143     c no flux to ocean bottom
144     if (ko.eq.Nr.or.hFacC(i,j,ko+1,bi,bj).eq.0.d0)
145     & flux_l=0.d0
146     endif
147    
148     c flux divergence
149     cflux(i,j,ko)=cflux(i,j,ko) +
150     & ( (flux_u-flux_l)/(drF(ko)*hFacC(i,j,ko,bi,bj)) )
151     c TEST ............................
152     c if(i .eq. 76 .and. j .eq. 36)then
153     c write(6,*)'k,flux_l/flux_u',ko,(flux_l/flux_u)
154     c write(6,*)'k,flux_l,cflux ',ko,flux_l,cflux(i,j,ko)
155     c endif
156     c TEST ............................
157     else
158     c if no layer below initial layer, remineralize
159     if (ko.eq.k+1) then
160     if (iflx.eq.1.and.omegaC(i,j,k,bi,bj) .gt. 1.d0) then
161     c ... at surface
162     cflux(i,j,1)=cflux(i,j,1)
163     & +bioac(i,j,k)*(1.0-DOPfraction)*
164     & R_cp*rain_ratio(i,j,bi,bj)
165     & *drF(k)*hFacC(i,j,k,bi,bj)/
166     & (drF(1)*hFacC(i,j,1,bi,bj) )
167     else
168     c ... at bottom
169     cflux(i,j,k)=cflux(i,j,k)
170     & +bioac(i,j,k)*(1.0-DOPfraction)*
171     & R_cp*rain_ratio(i,j,bi,bj)
172     endif
173     endif
174     endif
175     ENDDO
176    
177     endif
178     ENDDO
179     c diagnostic
180     c flx_tot=0
181     c k=0
182     c do k=1,nR
183     c flx_tot=flx_tot+cflux(i,j,k)*drF(k)*hFacC(i,j,k,bi,bj)
184     c if (hFacC(i,j,k,bi,bj).gt.0) then
185     c knum=k
186     c omeg_bot=omegaC(i,j,k,bi,bj)
187     c endif
188     c enddo
189     c if (hFacC(i,j,k,bi,bj).gt.0) then
190     c tmp=abs(exp_tot-flx_tot)
191     c if (tmp>1e-20) then
192     c print*,'QQ car_flux', knum,
193     c & omeg_bot, exp_tot, flx_tot, exp_tot-flx_tot
194     c endif
195     c endif
196     c end diagnostic
197     ENDDO
198     ENDDO
199     c
200     #endif
201     #endif
202     RETURN
203     END

  ViewVC Help
Powered by ViewVC 1.1.22