/[MITgcm]/MITgcm_contrib/torge/grease/code/seaice_tracer_phys.F
ViewVC logotype

Contents of /MITgcm_contrib/torge/grease/code/seaice_tracer_phys.F

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


Revision 1.1 - (show annotations) (download)
Thu Jan 16 23:37:42 2014 UTC (11 years, 6 months ago) by torge
Branch: MAIN
CVS Tags: HEAD
introducing a grease ice category
by making use of the seaice_tracer infrastructure

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_tracer_phys.F,v 1.10 2013/08/11 02:31:12 jmc Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE SEAICE_TRACER_PHYS( myTime, myIter, myThid )
8 C *=======================================================*
9 C | SUBROUTINE seaice_tracer_phys
10 C | o Time step SItr/SItrEFF as a result of
11 C | seaice thermodynamics and specific tracer physics
12 C *=======================================================*
13 IMPLICIT NONE
14
15 C === Global variables ===
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "FFIELDS.h"
20 #include "DYNVARS.h"
21 #include "SEAICE_SIZE.h"
22 #include "SEAICE.h"
23 #include "SEAICE_PARAMS.h"
24 #include "SEAICE_TRACER.h"
25 #ifdef ALLOW_SALT_PLUME
26 # include "SALT_PLUME.h"
27 #endif
28
29 C === Routine arguments ===
30 C INPUT:
31 C myTime :: Simulation time
32 C myIter :: Simulation timestep number
33 C myThid :: Thread no. that called this routine.
34 C OUTPUT:
35 _RL myTime
36 INTEGER myIter, myThid
37 CEndOfInterface
38
39 C === Local variables ===
40 #ifdef ALLOW_SITRACER
41
42 INTEGER iTr, jTh, I, J, bi, bj, ks
43 _RL SItrFromOcean (1:sNx,1:sNy)
44 _RL SItrFromFlood (1:sNx,1:sNy)
45 _RL HEFFprev, HEFFpost, growFact, meltPart, tmpscal1
46 _RL SItrExpand (1:sNx,1:sNy)
47 _RL AREAprev, AREApost, expandFact
48 CHARACTER*8 diagName
49
50 #ifdef ALLOW_SITRACER_DEBUG_DIAG
51 _RL DIAGarray (1:sNx,1:sNy,Nr)
52 #endif
53
54 cgf for now I do not fully account for ocean-ice fluxes of tracer
55 cgf -> I just prescribe it consistent with age tracer
56 cgf eventually I will need to handle them as function params
57
58 ks=1
59
60
61 DO bj=myByLo(myThid),myByHi(myThid)
62 DO bi=myBxLo(myThid),myBxHi(myThid)
63 DO iTr=1,SItrNumInUse
64
65 c 0) set ice-ocean and ice-snow exchange values
66 c =============================================
67 DO J=1,sNy
68 DO I=1,sNx
69 SItrFromOcean(i,j)=SItrFromOcean0(iTr)
70 SItrFromFlood(i,j)=SItrFromFlood0(iTr)
71 SItrExpand(i,j)=SItrExpand0(iTr)
72 ENDDO
73 ENDDO
74 c salinity tracer:
75 if ( (SItrName(iTr).EQ.'salinity').AND.
76 & (SItrFromOceanFrac(iTr).GT.ZERO) ) then
77 DO J=1,sNy
78 DO I=1,sNx
79 SItrFromOcean(i,j)=SItrFromOceanFrac(iTr)*salt(I,j,ks,bi,bj)
80 SItrFromFlood(i,j)=SItrFromFloodFrac(iTr)*salt(I,j,ks,bi,bj)
81 ENDDO
82 ENDDO
83 endif
84 c 1) seaice thermodynamics processes
85 c ==================================
86 if (SItrMate(iTr).EQ.'HEFF') then
87 DO J=1,sNy
88 DO I=1,sNx
89 HEFFprev=SItrHEFF(i,j,bi,bj,1)
90 #ifdef ALLOW_SITRACER_DEBUG_DIAG
91 DIAGarray(I,J,5+(iTr-1)*5) =
92 & HEFFprev*SItracer(i,j,bi,bj,iTr) + SItrBucket(i,j,bi,bj,iTr)
93 #endif
94 c apply the sequence of thermodynamics increments to actual traceur
95 c (see seaice_growth.F)
96 c (jTh=1 tendency due to ice-ocean interaction)
97 c (jTh=2 tendency due to the atmosphere, over ice covered part)
98 c (jTh=3 tendency due to the atmosphere, over open water part)
99 c (jTh=4 tendency due to flooding)
100 DO jTh=1,3
101 HEFFprev=SItrHEFF(i,j,bi,bj,jTh)
102 HEFFpost=SItrHEFF(i,j,bi,bj,jTh+1)
103 c compute ratio in [0. 1.] range for either growth or melt
104 growFact=1. _d 0
105 meltPart=0. _d 0
106 if (HEFFpost.GT.HEFFprev) growFact=HEFFprev/HEFFpost
107 if (HEFFpost.LT.HEFFprev) meltPart=HEFFprev-HEFFpost
108 c update SItr accordingly
109 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)*growFact
110 & +SItrFromOcean(i,j)*(1. _d 0 - growFact)
111 SItrBucket(i,j,bi,bj,iTr)=SItrBucket(i,j,bi,bj,iTr)
112 & -HEFFpost*SItrFromOcean(i,j)*(1. _d 0 - growFact)
113 SItrBucket(i,j,bi,bj,iTr)=SItrBucket(i,j,bi,bj,iTr)
114 & +meltPart*SItracer(i,j,bi,bj,iTr)
115 ENDDO
116 c apply flooding term
117 growFact=1. _d 0
118 HEFFprev=SItrHEFF(i,j,bi,bj,4)
119 HEFFpost=SItrHEFF(i,j,bi,bj,5)
120 if (HEFFpost.GT.HEFFprev) growFact=HEFFprev/HEFFpost
121 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)*growFact
122 & +SItrFromFlood(i,j) *(1. _d 0 - growFact)
123 c rk: flooding can only imply an ocean-ice tracer exchange, as long
124 c as we dont have snow tracers, so it goes through SItrBucket.
125 SItrBucket(i,j,bi,bj,iTr)=SItrBucket(i,j,bi,bj,iTr)
126 & -HEFFpost*SItrFromFlood(i,j)*(1. _d 0 - growFact)
127 #ifdef ALLOW_SITRACER_DEBUG_DIAG
128 DIAGarray(I,J,5+(iTr-1)*5) = HEFFpost*SItracer(i,j,bi,bj,iTr)
129 & +SItrBucket(i,j,bi,bj,iTr)-DIAGarray(I,J,5+(iTr-1)*5)
130 #endif
131 ENDDO
132 ENDDO
133 c TAF? if (SItrMate(iTr).EQ.'AREA') then
134 else
135 c 1) or seaice cover expansion
136 c ============================
137 c this is much simpler than for ice volume/mass tracers, because
138 c properties of the ice surface are not be conserved across the
139 c ocean-ice system, the contraction/expansion terms are all
140 c simultaneous (which is sane), and the only generic effect
141 c is due to expansion (new cover).
142 DO J=1,sNy
143 DO I=1,sNx
144 c apply expansion
145 AREAprev=SItrAREA(i,j,bi,bj,2)
146 AREApost=SItrAREA(i,j,bi,bj,3)
147 c compute ratio in [0. 1.] range for expansion/contraction
148 expandFact=1. _d 0
149 if (AREApost.GT.AREAprev) expandFact=AREAprev/AREApost
150 c update SItr accordingly
151 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)*expandFact
152 & +SItrExpand(i,j)*(1. _d 0 - expandFact)
153 ENDDO
154 ENDDO
155 endif
156 c 2) very ice tracer processes
157 c ============================
158 if (SItrName(iTr).EQ.'age') then
159 c age tracer: grow old as time passes by
160 DO J=1,sNy
161 DO I=1,sNx
162 if (( (SItrHEFF(i,j,bi,bj,5).GT.0. _d 0).AND.(SItrMate(iTr)
163 & .EQ.'HEFF') ).OR.( (SItrAREA(i,j,bi,bj,3).GT.0. _d 0).AND.
164 & (SItrMate(iTr).EQ.'AREA') )) then
165 SItracer(i,j,bi,bj,iTr)=
166 & SItracer(i,j,bi,bj,iTr)+SEAICE_deltaTtherm
167 else
168 SItracer(i,j,bi,bj,iTr)=0. _d 0
169 endif
170 ENDDO
171 ENDDO
172 elseif (SItrName(iTr).EQ.'salinity') then
173 c salinity tracer: no specific process
174 elseif (SItrName(iTr).EQ.'one') then
175 c "ice concentration" tracer: no specific process
176 elseif (SItrName(iTr).EQ.'ridge') then
177 c simple, made up, ice surface roughness index prototype
178 DO J=1,sNy
179 DO I=1,sNx
180 c ridging increases roughness
181 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)+
182 & MAX(0. _d 0, SItrAREA(i,j,bi,bj,1)-SItrAREA(i,j,bi,bj,2))
183 c ice melt reduces ridges/roughness
184 HEFFprev=SItrHEFF(i,j,bi,bj,1)
185 HEFFpost=SItrHEFF(i,j,bi,bj,4)
186 tmpscal1=1. _d 0
187 if (HEFFprev.GT.HEFFpost) tmpscal1=HEFFpost/HEFFprev
188 SItracer(i,j,bi,bj,iTr)=SItracer(i,j,bi,bj,iTr)*tmpscal1
189 ENDDO
190 ENDDO
191 endif
192 c 3) ice-ocean tracer exchange/mapping to external variables
193 c ==========================================================
194 #ifdef ALLOW_DIAGNOSTICS
195 IF ( useDiagnostics .AND. SItrMate(iTr).EQ.'HEFF') THEN
196 WRITE(diagName,'(A4,I2.2,A2)') 'SItr',iTr,'Fx'
197 tmpscal1=-ONE/SEAICE_deltaTtherm*SEAICE_rhoIce
198 CALL DIAGNOSTICS_SCALE_FILL(SItrBucket(1-OLx,1-OLy,bi,bj,iTr),
199 & tmpscal1, 1, diagName,0,1,2,bi,bj,myThid)
200 ENDIF
201 #endif
202
203 if ( (SItrName(iTr).EQ.'salinity').AND.
204 & (SEAICE_salinityTracer) ) then
205 c salinity tracer: salt flux
206 DO J=1,sNy
207 DO I=1,sNx
208 saltFlux(I,J,bi,bj) = - SItrBucket(i,j,bi,bj,iTr)
209 & *HEFFM(I,J,bi,bj)/SEAICE_deltaTtherm*SEAICE_rhoIce
210 c note: at this point of the time step, that is the correct sign
211 #ifdef ALLOW_SALT_PLUME
212 c should work for both constant and variable ice salinity -- to be tested
213 saltPlumeFlux(I,J,bi,bj) = MAX(ZERO,saltFlux(I,J,bi,bj))
214 & *SPsalFRAC*(salt(I,j,ks,bi,bj)-SItrFromOcean(i,j))
215 #endif
216 ENDDO
217 ENDDO
218 endif
219
220 DO J=1,sNy
221 DO I=1,sNx
222 #ifdef ALLOW_SITRACER_DEBUG_DIAG
223 DIAGarray(I,J,4+(iTr-1)*5) = - SItrBucket(i,j,bi,bj,iTr)
224 & *HEFFM(I,J,bi,bj)/SEAICE_deltaTtherm*SEAICE_rhoIce
225 #endif
226 c empty bucket
227 c but not for 'grease' (see seaice_growth.F)
228 if (SItrName(iTr).NE.'grease')
229 & SItrBucket(i,j,bi,bj,iTr)=0. _d 0
230 ENDDO
231 ENDDO
232
233 c TAF? elseif (SItrMate(iTr).EQ.'AREA') then
234
235 c 4) diagnostics
236 c ==============
237 #ifdef ALLOW_SITRACER_DEBUG_DIAG
238 if (SItrMate(iTr).EQ.'HEFF') then
239 DO J=1,sNy
240 DO I=1,sNx
241 HEFFpost=SItrHEFF(i,j,bi,bj,5)
242 DIAGarray(I,J,1+(iTr-1)*5) = SItracer(i,j,bi,bj,iTr)
243 DIAGarray(I,J,2+(iTr-1)*5) = SItracer(i,j,bi,bj,iTr)*HEFFpost
244 c DIAGarray(:,:,3) is the term of comparison for DIAGarray(:,:,2)
245 if (SItrName(iTr).EQ.'salinity') then
246 DIAGarray(I,J,3+(iTr-1)*5) = HSALT(i,j,bi,bj)/SEAICE_rhoIce
247 elseif (SItrName(iTr).EQ.'one') then
248 DIAGarray(I,J,3+(iTr-1)*5) = HEFFpost
249 endif
250 c DIAGarray(:,:,4) allows check of conservation : del(SItrBucket)+del(SItr*HEFF)=0. over do_phys
251 c DIAGarray(:,:,5) is the tracer flux from the ocean (<0 incr. ocean tracer)
252 ENDDO
253 ENDDO
254 else
255 DO J=1,sNy
256 DO I=1,sNx
257 AREApost=SItrAREA(i,j,bi,bj,3)
258 DIAGarray(I,J,1+(iTr-1)*5) = SItracer(i,j,bi,bj,iTr)
259 DIAGarray(I,J,2+(iTr-1)*5) = SItracer(i,j,bi,bj,iTr)*AREApost
260 ENDDO
261 ENDDO
262 endif
263 #endif
264 ENDDO
265 #ifdef ALLOW_SITRACER_DEBUG_DIAG
266 c CALL DIAGNOSTICS_FILL(DIAGarray,'UDIAG1 ',0,Nr,3,bi,bj,myThid)
267 #endif
268 ENDDO
269 ENDDO
270
271 #endif /* ALLOW_SITRACER */
272
273 RETURN
274 END

  ViewVC Help
Powered by ViewVC 1.1.22