/[MITgcm]/MITgcm/verification/tutorial_global_oce_latlon/code/ptracers_forcing_surf.F
ViewVC logotype

Contents of /MITgcm/verification/tutorial_global_oce_latlon/code/ptracers_forcing_surf.F

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


Revision 1.7 - (show annotations) (download)
Tue Apr 4 00:17:59 2017 UTC (7 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.6: +11 -4 lines
bring up to date from standard code in pkg/ptracers

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_forcing_surf.F,v 1.11 2012/03/08 17:13:31 jmc Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: PTRACERS_FORCING_SURF
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE PTRACERS_FORCING_SURF(
11 I relaxForcingS,
12 I bi, bj, iMin, iMax, jMin, jMax,
13 I myTime,myIter,myThid )
14
15 C !DESCRIPTION:
16 C Precomputes surface forcing term for pkg/ptracers.
17 C Precomputation is needed because of non-local KPP transport term,
18 C routine KPP_TRANSPORT_PTR.
19
20 C !USES: ===============================================================
21 IMPLICIT NONE
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "GRID.h"
26 #include "SURFACE.h"
27 #include "DYNVARS.h"
28 #include "FFIELDS.h"
29 #include "PTRACERS_SIZE.h"
30 #include "PTRACERS_PARAMS.h"
31 #include "PTRACERS_START.h"
32 #include "PTRACERS_FIELDS.h"
33
34 C !INPUT PARAMETERS: ===================================================
35 C relaxForcingS :: Salt forcing due to surface relaxation
36 C bi,bj :: tile indices
37 C myTime :: model time
38 C myIter :: time-step number
39 C myThid :: thread number
40 _RL relaxForcingS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 INTEGER bi, bj, iMin, iMax, jMin, jMax
42 _RL myTime
43 INTEGER myIter
44 INTEGER myThid
45
46 #ifdef ALLOW_PTRACERS
47
48 C !LOCAL VARIABLES: ====================================================
49 C i,j :: loop indices
50 C iTrc :: tracer index
51 C ks :: surface level index
52 INTEGER i, j
53 INTEGER iTrc, ks
54 _RL add2EmP(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55 _RL epsil, cutoff, tmpVar
56 CEOP
57
58 IF ( usingPCoords ) THEN
59 ks = Nr
60 ELSE
61 ks = 1
62 ENDIF
63
64 C Example of how to add forcing at the surface
65 DO iTrc=1,PTRACERS_numInUse
66 c IF ( PTRACERS_StepFwd(iTrc) ) THEN
67 DO j = jMin, jMax
68 DO i = iMin, iMax
69 C- Case of age-tracer: at the surface, add 10.days relaxation towards zero:
70 surfaceForcingPTr(i,j,bi,bj,iTrc) =
71 & + 1. _d 0 / (10. _d 0 * 86400. _d 0)
72 & * ( 0. _d 0 - pTracer(i,j,ks,bi,bj,iTrc) )
73 & * drF(ks) * _hFacC(i,j,ks,bi,bj)
74 ENDDO
75 ENDDO
76 c ENDIF
77 ENDDO
78
79 C-- Option to convert Salt-relaxation into additional EmP contribution
80 IF ( PTRACERS_addSrelax2EmP ) THEN
81 C- here we assume that salt_EvPrRn = 0
82 C set cutoff value to prevent too large additional EmP:
83 C current limit is set to 0.1 CFL
84 epsil = 1. _d -10
85 cutoff = 0.1 _d 0 *drF(ks)/PTRACERS_dTLev(ks)
86 IF ( ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
87 & .AND. useRealFreshWaterFlux )
88 & .OR.convertFW2Salt .EQ. -1. ) THEN
89 DO j = jMin, jMax
90 DO i = iMin, iMax
91 tmpVar = MAX( salt(i,j,ks,bi,bj), epsil )
92 add2EmP(i,j) = relaxForcingS(i,j)/tmpVar
93 add2EmP(i,j) = rUnit2mass
94 & *MAX( -cutoff, MIN( add2EmP(i,j), cutoff ) )
95 ENDDO
96 ENDDO
97 ELSE
98 DO j = jMin, jMax
99 DO i = iMin, iMax
100 add2EmP(i,j) = relaxForcingS(i,j)/convertFW2Salt
101 add2EmP(i,j) = rUnit2mass
102 & *MAX( -cutoff, MIN( add2EmP(i,j), cutoff ) )
103 ENDDO
104 ENDDO
105 ENDIF
106 #ifdef ALLOW_DIAGNOSTICS
107 IF ( useDiagnostics ) THEN
108 CALL DIAGNOSTICS_FILL(add2EmP,'Add2EmP ',0,1,2,bi,bj,myThid)
109 ENDIF
110 #endif /* ALLOW_DIAGNOSTICS */
111 ELSE
112 DO j = jMin, jMax
113 DO i = iMin, iMax
114 add2EmP(i,j) = 0. _d 0
115 ENDDO
116 ENDDO
117 ENDIF
118 C-- end of "addEmP" setting
119
120 #ifdef EXACT_CONSERV
121 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
122 & .AND. useRealFreshWaterFlux ) THEN
123
124 DO iTrc=1,PTRACERS_numInUse
125
126 c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
127 c the water column height ; temp., salt, (tracer) flux associated
128 c with this input/output of water is added here to the surface tendency.
129 c
130 IF ( PTRACERS_StepFwd(iTrc) .AND.
131 & PTRACERS_EvPrRn(iTrc).NE.UNSET_RL ) THEN
132 DO j = jMin, jMax
133 DO i = iMin, iMax
134 surfaceForcingPTr(i,j,bi,bj,iTrc) =
135 & surfaceForcingPTr(i,j,bi,bj,iTrc)
136 & + ( PmEpR(i,j,bi,bj) - add2EmP(i,j) )
137 & *( PTRACERS_EvPrRn(iTrc) - pTracer(i,j,ks,bi,bj,iTrc) )
138 & *mass2rUnit
139 ENDDO
140 ENDDO
141 ENDIF
142
143 ENDDO
144
145 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
146 ELSE
147 #else /* EXACT_CONSERV */
148 IF (.TRUE.) THEN
149 #endif /* EXACT_CONSERV */
150
151 C-- EmPmR does not really affect the water column height (for tracer budget)
152 C and is converted to a salt tendency.
153
154 IF (convertFW2Salt .EQ. -1.) THEN
155 C- use local surface tracer field to calculate forcing term:
156
157 DO iTrc=1,PTRACERS_numInUse
158
159 IF ( PTRACERS_StepFwd(iTrc) .AND.
160 & PTRACERS_EvPrRn(iTrc).NE.UNSET_RL ) THEN
161 C account for Rain/Evap tracer content (PTRACERS_EvPrRn) using
162 C local surface tracer
163 DO j = jMin, jMax
164 DO i = iMin, iMax
165 surfaceForcingPTr(i,j,bi,bj,iTrc) =
166 & surfaceForcingPTr(i,j,bi,bj,iTrc)
167 & + ( EmPmR(i,j,bi,bj) + add2EmP(i,j) )
168 & *( pTracer(i,j,ks,bi,bj,iTrc) - PTRACERS_EvPrRn(iTrc) )
169 & *mass2rUnit
170 ENDDO
171 ENDDO
172 ENDIF
173
174 ENDDO
175
176 ELSE
177 C- use uniform tracer value to calculate forcing term:
178
179 DO iTrc=1,PTRACERS_numInUse
180
181 IF ( PTRACERS_StepFwd(iTrc) .AND.
182 & PTRACERS_EvPrRn(iTrc).NE.UNSET_RL ) THEN
183 C account for Rain/Evap tracer content (PTRACERS_EvPrRn) assuming uniform
184 C surface tracer (=PTRACERS_ref)
185 DO j = jMin, jMax
186 DO i = iMin, iMax
187 surfaceForcingPTr(i,j,bi,bj,iTrc) =
188 & surfaceForcingPTr(i,j,bi,bj,iTrc)
189 & + ( EmPmR(i,j,bi,bj) + add2EmP(i,j) )
190 & *( PTRACERS_ref(ks,iTrc) - PTRACERS_EvPrRn(iTrc) )
191 & *mass2rUnit
192 ENDDO
193 ENDDO
194 ENDIF
195
196 ENDDO
197
198 C- end local-surface-tracer / uniform-value distinction
199 ENDIF
200
201 ENDIF
202
203 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
204
205 #endif /* ALLOW_PTRACERS */
206
207 RETURN
208 END

  ViewVC Help
Powered by ViewVC 1.1.22