/[MITgcm]/MITgcm/pkg/ptracers/ptracers_forcing_surf.F
ViewVC logotype

Annotation of /MITgcm/pkg/ptracers/ptracers_forcing_surf.F

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


Revision 1.10 - (hide annotations) (download)
Sun Sep 5 22:28:14 2010 UTC (13 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62k, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.9: +51 -5 lines
option (flag:PTRACERS_addSrelax2EmP) to convert Salt Relax into additional EmP

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

  ViewVC Help
Powered by ViewVC 1.1.22