/[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.7 - (hide annotations) (download)
Mon Apr 7 20:31:16 2008 UTC (16 years, 5 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint60, checkpoint61, checkpoint62, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y, HEAD
Changes since 1.6: +1 -2 lines
Moving dic options to DIC_OPTIONS.h

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

  ViewVC Help
Powered by ViewVC 1.1.22