/[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.14 - (show annotations) (download)
Mon Aug 2 13:54:18 2010 UTC (13 years, 11 months ago) by mlosch
Branch: MAIN
Changes since 1.13: +16 -3 lines
make the routines a six times faster on a vector computer when
NONLIN_FRSURF is undefined

1 C $Header: /u/gcmpack/MITgcm/pkg/dic/car_flux.F,v 1.13 2010/08/02 10:32:13 mlosch Exp $
2 C $Name: $
3
4 #include "DIC_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: CAR_FLUX
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE CAR_FLUX( CAR_S, cflux,
11 I bi,bj,imin,imax,jmin,jmax,
12 I myIter,myTime,myThid)
13
14 C !DESCRIPTION:
15 C Calculate carbonate fluxes
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_VARS.h"
25
26 C !INPUT PARAMETERS: ===================================================
27 C myThid :: thread number
28 C myIter :: current timestep
29 C myTime :: current time
30 C CAR_S :: carbonate source
31 INTEGER myIter
32 _RL myTime
33 INTEGER myThid
34 _RL CAR_S(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 #if (defined ALLOW_PTRACERS && defined DIC_BIOTIC)
42
43 C !LOCAL VARIABLES: ====================================================
44 C i,j,k :: loop indices
45 c ko :: loop-within-loop index
46 c caexport :: flux of carbonate from base each "productive"
47 c layer
48 c depth_l :: depth and lower interface
49 c flux_u, flux_l :: flux through upper and lower interfaces
50 c reminFac :: abbreviation
51 c zbase :: depth of bottom of current productive layer
52 INTEGER I,J,k, ko, kop1
53 _RL maskp1
54 _RL zbase
55 _RL caexport(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 _RL reminFac
57 _RL depth_l
58 _RL flux_u (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59 _RL flux_l
60 CEOP
61
62 C- Calculate carbonate flux from base of each layer
63 DO k=1,nlev
64 DO j=jmin,jmax
65 DO i=imin,imax
66 caexport(i,j) = 0. _d 0
67 IF (hFacC(i,j,k,bi,bj).GT.0. _d 0) THEN
68 C-- If no layer below initial layer (because of bottom or
69 C-- topography), then remineralize in here
70 IF (k.EQ.Nr) THEN
71 cflux(i,j,k)=cflux(i,j,k) + CAR_S(i,j,k)
72 ELSEIF (hFacC(i,j,k+1,bi,bj).EQ.0. _d 0) THEN
73 cflux(i,j,k)=cflux(i,j,k) + CAR_S(i,j,k)
74 ELSE
75 C- flux out of layer k
76 caexport(i,j) = CAR_S(i,j,k)*drF(k) * _hFacC(i,j,k,bi,bj)
77 ENDIF
78 ENDIF
79 ENDDO
80 ENDDO
81 C-- If availabe, flux carbon export downward;
82 C-- calculate flux to each layer from base of k
83 zbase=-rF(k+1)
84 C-- Upper flux
85 DO j=jmin,jmax
86 DO i=imin,imax
87 flux_u(i,j) = caexport(i,j)
88 ENDDO
89 ENDDO
90 DO ko=k+1,Nr
91 kop1 = MIN(Nr,ko+1)
92 maskp1 = 1. _d 0
93 IF (ko.GE.Nr) maskp1 = 0. _d 0
94 #ifndef NONLIN_FRSRURF
95 C For the linear free surface, hFacC can be omitted, buying another
96 C performance increase of a factor of six on a vector computer.
97 C For now this is not implemented via run time flags, in order to
98 C avoid making this code too complicated.
99 depth_l = -rF(ko) + drF(ko)
100 reminFac = exp(-(depth_l-zbase)/zca)
101 #endif
102 DO j=jmin,jmax
103 DO i=imin,imax
104 IF ( caexport(i,j) .NE. 0. _d 0 ) THEN
105 C-- Lower flux (no flux to ocean bottom)
106 #ifdef NONLIN_FRSRURF
107 depth_l = -rF(ko) + drF(ko) * _hFacC(i,j,ko,bi,bj)
108 reminFac = exp(-(depth_l-zbase)/zca)
109 #endif
110 flux_l = caexport(i,j)*reminFac
111 & *maskp1*maskC(i,j,kop1,bi,bj)
112
113 cflux(i,j,ko)=cflux(i,j,ko) + (flux_u(i,j)-flux_l)
114 & *recip_drF(ko)*recip_hFacC(i,j,ko,bi,bj)
115 C-- Store flux through upper layer for the next k-level
116 flux_u(i,j) = flux_l
117
118 C endif carexport .ne. 0
119 ENDIF
120 C i,j-loops
121 ENDDO
122 ENDDO
123 C ko-loop
124 ENDDO
125 C k-loop
126 ENDDO
127 c
128 #endif /* defined ALLOW_PTRACERS && defined DIC_BIOTIC */
129 RETURN
130 END

  ViewVC Help
Powered by ViewVC 1.1.22