/[MITgcm]/MITgcm/pkg/salt_plume/salt_plume_volfrac.F
ViewVC logotype

Contents of /MITgcm/pkg/salt_plume/salt_plume_volfrac.F

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


Revision 1.2 - (show annotations) (download)
Wed May 21 13:59:39 2014 UTC (10 years ago) by atn
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, 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, checkpoint65, HEAD
Changes since 1.1: +2 -2 lines
minor bug fix for correct tile

1 C $Header: /u/gcmpack/MITgcm/pkg/salt_plume/salt_plume_volfrac.F,v 1.1 2014/05/21 10:52:21 heimbach Exp $
2 C $Name: $
3
4 #include "SALT_PLUME_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: SALT_PLUME_VOLFRAC
8 C !INTERFACE:
9 SUBROUTINE SALT_PLUME_VOLFRAC(
10 I bi, bj, myTime, myIter, myThid )
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE SALT_PLUME_VOLFRAC
15 C | o Compute saltplume penetration.
16 C *==========================================================*
17 C | Compute fraction of volume flux associated with saltplume
18 C | flux penetrating through the entire water columns due to
19 C | rejected salt during freezing.
20 C |
21 C | For example, if surface value is Saltplume0,
22 C | and each level gets equal fraction 1/5 down to SPDepth=5,
23 C | SALT_PLUME_VOLFRAC will report
24 C | dSPvolkLev2Above[2to1,3to2,4to3,5to4,6to5] = [4/5,3/5,2/5,1/5, 0]
25 C | dSPvolSurf2kLev [1to1,1to2,1to3,1to4,1to5] = [1/5,1/5,1/5,1/5,1/5]
26 C | sum [into5] = 1to5 + 6to5 - 5to4 = 1/5 + 0 - 1/5 = 0
27 C | [into4] = 1to4 + 5to4 - 4to3 = 1/5 + 1/5 - 2/5 = 0
28 C | [into3] = 1to3 + 4to3 - 3to2 = 1/5 + 2/5 - 3/5 = 0
29 C | [into2] = 1to2 + 3to2 - 2to1 = 1/5 + 3/5 - 4/5 = 0
30 C | [into1] = 1to1 + 2to1 - 1to[1,2,3,4,5] = 1/5 + 4/5 - 5/5 = 0
31 C | NOTE: volume will always be conserved.
32 C | =====
33 C | Written by : ATN (based on SALT_PLUME_FRAC)
34 C | Date : Apr 14, 2014
35 C *==========================================================*
36 C \ev
37
38 C !USES:
39 IMPLICIT NONE
40 #include "SIZE.h"
41 #include "GRID.h"
42 #include "SALT_PLUME.h"
43 #include "EEPARAMS.h"
44 #include "PARAMS.h"
45
46 C !INPUT/OUTPUT PARAMETERS:
47 C input arguments
48 C SPDpeth :: corresponding SaltPlumeDepth(i,j) at this grid point
49 C myTime :: Current time in simulation
50 C myIter :: Current iteration number in simulation
51 C myThid :: My Thread Id. number
52 INTEGER bi,bj
53 _RL myTime
54 INTEGER myIter
55 INTEGER myThid
56 C input/output arguments
57 C CHARACTER*(MAX_LEN_MBUF) msgBuf
58 CEOP
59
60 #ifdef ALLOW_SALT_PLUME
61 #ifdef SALT_PLUME_VOLUME
62
63 C !LOCAL VARIABLES:
64 _RL dMbdt (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65 _RL temp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
66 _RL dplumek
67 INTEGER SPkBottom (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68 INTEGER i,j,k,kp1,Nlev,Nrp1
69 INTEGER imt
70 parameter( imt=(sNx+2*OLx)*(sNy+2*OLy) )
71
72 C initialize at every time step
73 Nrp1=Nr+1
74 DO k=1,Nr
75 DO j=1-OLy,sNy+OLy
76 DO i=1-OLx,sNx+OLx
77 dSPvolSurf2kLev(i,j,k,bi,bj) = 0. _d 0
78 dSPvolkLev2Above(i,j,k,bi,bj) = 0. _d 0
79 SPplumek(i,j,k,bi,bj) = 1. _d 0
80 ENDDO
81 ENDDO
82 ENDDO
83 DO j=1-OLy,sNy+OLy
84 DO i=1-OLx,sNx+OLx
85 SPplumek(i,j,Nrp1,bi,bj) = 1. _d 0
86 SPbrineVolFlux(i,j,bi,bj) = 0. _d 0
87 SPkBottom(i,j) = 0
88 ENDDO
89 ENDDO
90
91 C call salt_plume_frac to fill in SPplumek and SPkBottom
92 C use dMbdt+temp as a temporary arrays here to save memory:
93 DO k = Nrp1,1,-1
94 DO j=1-Oly,sNy+Oly
95 DO i=1-Olx,sNx+Olx
96 temp(i,j)=SaltPlumeDepth(i,j,bi,bj)
97 dMbdt(i,j)=abs(rF(k))
98 ENDDO
99 ENDDO
100 CALL SALT_PLUME_FRAC(
101 I imt,oneRS,temp,
102 #ifdef SALT_PLUME_SPLIT_BASIN
103 I XC(1-Olx,1-Oly,bi,bj),YC(1-Olx,1-Oly,bi,bj),
104 #endif
105 U dMbdt,
106 I myTime, 1, myThid )
107 DO j=1-Oly,sNy+Oly
108 DO i=1-Olx,sNx+Olx
109 SPplumek(i,j,k,bi,bj)=dMbdt(i,j)
110 IF(SPplumek(i,j,k,bi,bj).GT. 0.9999999) THEN
111 SPkBottom(i,j)=k
112 ENDIF
113 ENDDO
114 ENDDO
115 ENDDO
116
117 C reinitialize dMbdt = 0
118 DO j=1-Oly,sNy+Oly
119 DO i=1-Olx,sNx+Olx
120 dMbdt(i,j)=0. _d 0
121 ENDDO
122 ENDDO
123
124 C Now calculating dplumek, dSPvolumeUp, dSPvolSurf2kLev
125 C units:
126 C Sbrine=dsb/dt*dt/(rhoConst*SPalpha*drF)[psu kg/m2/s*s/(kg/m3*m)]=[psu]
127 C SPplumek : fraction : unitless
128 C SaltPlumeFlux: dsb/dt [psu.kg/m^2/s = g/m^2/s]
129 C brine_mass_flux dMb/dt = dsb/dt / Sbrine [kg/m2/s]
130 C = dsb/dt / (dsb/dt*dt/(rhoConst*SPalpha*drF))
131 C = rhoConst*SPalpha*drF/dt [kg/m3 m/s]=[kg/m2/s]
132 C dVbrine/dt = dMb/dt 1/rhoConst [m/s]
133
134 C has 2 ways to define brine properties: either provide
135 C (A) SPalpha: vol frac or (B) SPbrineSalt: brine salinity.
136 C (A) SPalpha: can calc SPbrineSalt as fxn of dhice/dt,
137 C constrained by SPbrineSaltmax:
138 C SPbrineSalt=SaltPlumeFlux/rhoConst/SPalpha/drF(1)*dt
139 C SPbrineSalt=min(SPbrineSalt,SPbrineSaltmax)
140 C dMbdt = saltPlumeFlux / SPbrineSalt
141 C = rhoConst*SPalpha*drF(1)/dt <-- a function of SPalpha
142 C (B) SPbrinesalt provided
143 C dMbdt = saltPlumeFlux / SPbrineSalt <-- fxn of SPbrineSalt
144
145 C Assuming we go with (B) here:
146 DO j=1-OLy,sNy+OLy
147 DO i=1-OLx,sNx+OLx
148 C brine mass and volume at surface:
149 dMbdt(i,j)=saltPlumeFlux(i,j,bi,bj)/SPbrineSconst
150 SPbrineVolFlux(i,j,bi,bj)=dMbdt(i,j)*mass2rUnit
151 ENDDO
152 ENDDO
153
154 C Distributing down: this is always from level 1 to depth
155 DO k=Nr,1,-1
156 DO j=1-OLy,sNy+OLy
157 DO i=1-OLx,sNx+OLx
158 dplumek=SPplumek(i,j,k+1,bi,bj)-SPplumek(i,j,k,bi,bj)
159 dSPvolSurf2kLev(i,j,k,bi,bj)=dplumek*SPbrineVolFlux(i,j,bi,bj)
160 ENDDO
161 ENDDO
162 ENDDO
163
164 C Now volume up: need to scan from bottom of SPDepth
165 DO j=1-OLy,sNy+OLy
166 DO i=1-OLx,sNx+OLx
167 Nlev=SPkBottom(i,j)
168 IF(Nlev.GE.1 .AND. Nlev.LE.Nr) THEN
169 DO k=Nlev,1,-1
170 kp1=k+1
171 dSPvolkLev2Above(i,j,k,bi,bj)=dSPvolkLev2Above(i,j,kp1,bi,bj)
172 & - dSPvolSurf2kLev(i,j,k,bi,bj)
173 ENDDO
174 ENDIF
175 ENDDO
176 ENDDO
177
178 #ifdef ALLOW_DIAGNOSTICS
179 IF ( useDiagnostics ) THEN
180 CALL DIAGNOSTICS_FILL(
181 & SPplumek,'PLUMEKB1',0,Nr,1,bi,bj,myThid )
182 ENDIF
183 #endif /* ALLOW_DIAGNOSTICS */
184
185 #endif /* SALT_PLUME_VOLUME */
186 #endif /* ALLOW_SALT_PLUME */
187
188 RETURN
189 END

  ViewVC Help
Powered by ViewVC 1.1.22