/[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.1 - (hide annotations) (download)
Thu Aug 18 19:46:45 2005 UTC (18 years, 10 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint57q_post
o new routine needed for calcium carbonate dissolution scheme of Karsten Friis

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

  ViewVC Help
Powered by ViewVC 1.1.22