/[MITgcm]/MITgcm/model/src/external_forcing_surf.F
ViewVC logotype

Contents of /MITgcm/model/src/external_forcing_surf.F

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


Revision 1.16 - (show annotations) (download)
Fri Oct 24 05:29:35 2003 UTC (20 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint51o_pre, checkpoint52, checkpoint51t_post, checkpoint51s_post, checkpoint52b_pre, checkpoint51q_post, checkpoint52b_post, checkpoint52c_post, checkpoint51r_post, checkpoint52a_pre, branch-netcdf, checkpoint51o_post, checkpoint52a_post, ecco_c52_e35, checkpoint51p_post, checkpoint51u_post
Branch point for: branch-nonh
Changes since 1.15: +97 -86 lines
 o undid all of the cp51 checkin pending some ongoing code cleanups
   and discussion

1 C $Header: /u/u3/gcmpack/MITgcm/model/src/external_forcing_surf.F,v 1.14 2003/10/16 23:46:47 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: EXTERNAL_FORCING_SURF
9 C !INTERFACE:
10 SUBROUTINE EXTERNAL_FORCING_SURF(
11 I bi, bj, iMin, iMax, jMin, jMax,
12 I myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | SUBROUTINE EXTERNAL_FORCING_SURF
16 C | o Determines forcing terms based on external fields
17 C | relaxation terms etc.
18 C *==========================================================*
19 C \ev
20
21 C !USES:
22 IMPLICIT NONE
23 C === Global variables ===
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "FFIELDS.h"
28 #include "DYNVARS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31
32 C !INPUT/OUTPUT PARAMETERS:
33 C === Routine arguments ===
34 C myTime - Current time in simulation
35 C myIter - Current iteration number in simulation
36 C myThid :: Thread no. that called this routine.
37 _RL myTime
38 INTEGER myIter
39 INTEGER myThid
40 INTEGER bi,bj
41 INTEGER iMin, iMax
42 INTEGER jMin, jMax
43
44 C !LOCAL VARIABLES:
45 C === Local variables ===
46 INTEGER i,j
47 C number of surface interface layer
48 INTEGER kSurface
49 CEOP
50
51 if ( buoyancyRelation .eq. 'OCEANICP' ) then
52 kSurface = Nr
53 else
54 kSurface = 1
55 endif
56
57 C-- Surface Fluxes :
58
59 DO j = jMin, jMax
60 DO i = iMin, iMax
61
62 c Zonal wind stress fu:
63 surfaceTendencyU(i,j,bi,bj) =
64 & fu(i,j,bi,bj)*horiVertRatio*recip_rhoConst
65 & *recip_drF(kSurface)*recip_hFacW(i,j,kSurface,bi,bj)
66 c Meridional wind stress fv:
67 surfaceTendencyV(i,j,bi,bj) =
68 & fv(i,j,bi,bj)*horiVertRatio*recip_rhoConst
69 & *recip_drF(kSurface)*recip_hFacS(i,j,kSurface,bi,bj)
70 c Net heat flux Qnet:
71 surfaceTendencyT(i,j,bi,bj) =
72 & -Qnet(i,j,bi,bj)*recip_Cp*horiVertRatio*recip_rhoConst
73 & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
74 C Net Salt Flux :
75 surfaceTendencyS(i,j,bi,bj) =
76 & -saltFlux(i,j,bi,bj)*horiVertRatio*recip_rhoConst
77 & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
78
79 #ifdef ALLOW_PASSIVE_TRACER
80 c *** define the tracer surface tendency here ***
81 #endif /* ALLOW_PASSIVE_TRACER */
82
83 ENDDO
84 ENDDO
85
86 C-- Surface restoring term :
87
88 IF ( doThetaClimRelax .OR. doSaltClimRelax ) THEN
89 DO j = jMin, jMax
90 DO i = iMin, iMax
91 C Heat Flux (restoring term) :
92 IF ( abs(yC(i,j,bi,bj)).LE.latBandClimRelax ) THEN
93 surfaceTendencyT(i,j,bi,bj) = surfaceTendencyT(i,j,bi,bj)
94 & -lambdaThetaClimRelax
95 & *(theta(i,j,kSurface,bi,bj)-SST(i,j,bi,bj))
96 C Salt Flux (restoring term) :
97 surfaceTendencyS(i,j,bi,bj) = surfaceTendencyS(i,j,bi,bj)
98 & -lambdaSaltClimRelax
99 & *(salt(i,j,kSurface,bi,bj)-SSS(i,j,bi,bj))
100 ENDIF
101 ENDDO
102 ENDDO
103 ENDIF
104
105 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
106 C-- Fresh-water flux
107
108 #ifdef NONLIN_FRSURF
109 IF ( (nonlinFreeSurf.GT.0 .OR. buoyancyRelation.EQ.'OCEANICP')
110 & .AND. useRealFreshWaterFlux ) THEN
111
112 c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
113 c the water column height ; temp., salt, (tracer) flux associated
114 c with this input/output of water is added here to the surface tendency.
115 c
116 c NB: PmEpR lag 1 time step behind EmPmR ( PmEpR_n = - EmPmR_n-1 ) to stay
117 c consitent with volume change (=d/dt etaN).
118
119 IF (temp_EvPrRn.NE.UNSET_RL) THEN
120 DO j = jMin, jMax
121 DO i = iMin, iMax
122 surfaceTendencyT(i,j,bi,bj) = surfaceTendencyT(i,j,bi,bj)
123 & + PmEpR(i,j,bi,bj)
124 & *( temp_EvPrRn - theta(i,j,kSurface,bi,bj) )
125 & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
126 & *convertEmP2rUnit
127 ENDDO
128 ENDDO
129 ENDIF
130
131 IF (salt_EvPrRn.NE.UNSET_RL) THEN
132 DO j = jMin, jMax
133 DO i = iMin, iMax
134 surfaceTendencyS(i,j,bi,bj) = surfaceTendencyS(i,j,bi,bj)
135 & + PmEpR(i,j,bi,bj)
136 & *( salt_EvPrRn - salt(i,j,kSurface,bi,bj) )
137 & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
138 & *convertEmP2rUnit
139 ENDDO
140 ENDDO
141 ENDIF
142
143 #ifdef ALLOW_PASSIVE_TRACER
144 c *** add the tracer flux associated with P-E+R here ***
145 c IF (trac_EvPrRn.NE.UNSET_RL) THEN
146 c & + PmEpR(i,j,bi,bj)*( trac_EvPrRn - tr1(i,j,kSurface,bi,bj) )
147 c & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
148 c ENDIF
149 #endif /* ALLOW_PASSIVE_TRACER */
150
151 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
152 ELSE
153 #else /* NONLIN_FRSURF */
154 IF (.TRUE.) THEN
155 #endif /* NONLIN_FRSURF */
156
157 c- EmPmR does not really affect the water column height (for tracer budget)
158 c and is converted to a salt tendency.
159
160 IF (convertFW2Salt .EQ. -1.) THEN
161 c- converts EmPmR to salinity tendency using surface local salinity
162 DO j = jMin, jMax
163 DO i = iMin, iMax
164 surfaceTendencyS(i,j,bi,bj) = surfaceTendencyS(i,j,bi,bj)
165 & + EmPmR(i,j,bi,bj)*salt(i,j,kSurface,bi,bj)
166 & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
167 & *convertEmP2rUnit
168 ENDDO
169 ENDDO
170 ELSE
171 c- converts EmPmR to virtual salt flux using uniform salinity (default=35)
172 DO j = jMin, jMax
173 DO i = iMin, iMax
174 surfaceTendencyS(i,j,bi,bj) = surfaceTendencyS(i,j,bi,bj)
175 & + EmPmR(i,j,bi,bj)*convertFW2Salt
176 & *recip_drF(kSurface)*recip_hFacC(i,j,kSurface,bi,bj)
177 & *convertEmP2rUnit
178 ENDDO
179 ENDDO
180 ENDIF
181
182 ENDIF
183 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
184 #ifdef ALLOW_PTRACERS
185 IF ( usePTRACERS ) THEN
186 CALL PTRACERS_FORCING_SURF(
187 I bi, bj, iMin, iMax, jMin, jMax,
188 I myTime,myIter,myThid )
189 ENDIF
190 #endif /* ALLOW_PTRACERS */
191
192 #ifdef ATMOSPHERIC_LOADING
193
194 C-- Atmospheric surface Pressure loading :
195
196 IF (buoyancyRelation .eq. 'OCEANIC' ) THEN
197 DO j = jMin, jMax
198 DO i = iMin, iMax
199 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)*recip_rhoConst
200 ENDDO
201 ENDDO
202 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
203 C-- This is a hack used to read phi0surf from a file (ploadFile)
204 C instead of computing it from bathymetry & density ref. profile.
205 C The true atmospheric P-loading is not yet implemented for P-coord
206 C (requires time varying dP(Nr) like dP(k-bottom) with NonLin FS).
207 DO j = jMin, jMax
208 DO i = iMin, iMax
209 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)
210 ENDDO
211 ENDDO
212 ENDIF
213
214 #endif /* ATMOSPHERIC_LOADING */
215
216 RETURN
217 END

  ViewVC Help
Powered by ViewVC 1.1.22