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

Contents of /MITgcm/pkg/dic/car_flux.F

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


Revision 1.5 - (show annotations) (download)
Fri Dec 16 21:07:53 2005 UTC (18 years, 6 months ago) by stephd
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58c_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58b_post, checkpoint58m_post
Changes since 1.4: +2 -2 lines
o dic code now does no calculations on the overlap regions

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( 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
15 C !USES: ===============================================================
16 IMPLICIT NONE
17 #include "SIZE.h"
18 #include "DYNVARS.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "GRID.h"
22 #include "DIC_BIOTIC.h"
23
24 C !INPUT PARAMETERS: ===================================================
25 C myThid :: thread number
26 C myIter :: current timestep
27 C myTime :: current time
28 C bioac :: biological productivity
29 INTEGER myIter
30 _RL myTime
31 INTEGER myThid
32 _RL bioac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
33 INTEGER imin, imax, jmin, jmax, bi, bj
34
35 C !OUTPUT PARAMETERS: ===================================================
36 C cflux :: carbonate flux
37 _RL cflux(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
38
39 #ifdef ALLOW_PTRACERS
40 #ifdef DIC_BIOTIC
41
42 C !LOCAL VARIABLES: ====================================================
43 C i,j,k :: loop indices
44 c ko :: loop-within-loop index
45 c caexport :: flux of carbonate from base each "productive"
46 c layer
47 c depth_u, depth_l :: depths of upper and lower interfaces
48 c flux_u, flux_l :: flux through upper and lower interfaces
49 c zbase :: depth of bottom of current productive layer
50 _RL caexport(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 INTEGER I,J,k, ko
52 _RL depth_u, depth_l
53 _RL flux_u, flux_l
54 _RL zbase
55 CEOP
56
57 c
58 c calculate carbonate flux from base of each nlev
59 DO j=jmin,jmax
60 DO i=imin,imax
61 DO k=1,nLev
62 if (hFacC(i,j,k,bi,bj).gt.0.d0) then
63 caexport(i,j)= R_cp*rain_ratio(i,j,bi,bj)*bioac(i,j,k)*
64 & (1.0-DOPfraction)*drF(k)*hFacC(i,j,k,bi,bj)
65 c calculate flux to each layer from base of k
66 zbase=-rF(k+1)
67 Do ko=k+1,Nr
68 if (hFacC(i,j,ko,bi,bj).gt.0.d0) then
69 depth_u=-rF(ko)
70 depth_l=depth_u+
71 & drF(ko)*hFacC(i,j,ko,bi,bj)
72 flux_u=caexport(i,j)*exp(-(depth_u-zbase)/zca)
73 c no flux to ocean bottom
74 if (ko.eq.Nr) then
75 flux_l=0.d0
76 else
77 if (hFacC(i,j,ko+1,bi,bj).eq.0.d0) then
78 flux_l=0.d0
79 else
80 flux_l=caexport(i,j)*exp(-(depth_l-zbase)/zca)
81 endif
82 endif
83 cflux(i,j,ko)=cflux(i,j,ko) +
84 & ( (Flux_u-Flux_l)/(drF(ko)*hFacC(i,j,ko,bi,bj)) )
85 else
86 c if no layer below initial layer, remineralize in place
87 if (ko.eq.k+1) cflux(i,j,k)=cflux(i,j,k)
88 & +bioac(i,j,k)*(1.0-DOPfraction)*
89 & R_cp*rain_ratio(i,j,bi,bj)
90 endif
91 ENDDO
92 endif
93 ENDDO
94 ENDDO
95 ENDDO
96 c
97 #endif
98 #endif
99 RETURN
100 END

  ViewVC Help
Powered by ViewVC 1.1.22