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

Annotation of /MITgcm/model/src/external_forcing.F

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


Revision 1.21 - (hide annotations) (download)
Sat Dec 6 00:08:35 2003 UTC (20 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52d_pre
Changes since 1.20: +37 -5 lines
add standard entry point for AIM.

1 jmc 1.21 C $Header: /u/gcmpack/MITgcm/model/src/external_forcing.F,v 1.20 2003/10/09 04:19:18 edhill Exp $
2 adcroft 1.12 C $Name: $
3 cnh 1.1
4 edhill 1.20 #include "PACKAGES_CONFIG.h"
5 cnh 1.1 #include "CPP_OPTIONS.h"
6 heimbach 1.19 #ifdef ALLOW_OBCS
7     # include "OBCS_OPTIONS.h"
8     #endif
9 cnh 1.1
10 cnh 1.13 CBOP
11     C !ROUTINE: EXTERNAL_FORCING_U
12     C !INTERFACE:
13 cnh 1.1 SUBROUTINE EXTERNAL_FORCING_U(
14     I iMin, iMax, jMin, jMax,bi,bj,kLev,
15     I myCurrentTime,myThid)
16 cnh 1.13 C !DESCRIPTION: \bv
17     C *==========================================================*
18     C | S/R EXTERNAL_FORCING_U
19     C | o Contains problem specific forcing for zonal velocity.
20     C *==========================================================*
21     C | Adds terms to gU for forcing by external sources
22     C | e.g. wind stress, bottom friction etc..................
23     C *==========================================================*
24     C \ev
25    
26     C !USES:
27 cnh 1.2 IMPLICIT NONE
28 cnh 1.1 C == Global data ==
29     #include "SIZE.h"
30     #include "EEPARAMS.h"
31     #include "PARAMS.h"
32     #include "GRID.h"
33     #include "DYNVARS.h"
34 cnh 1.2 #include "FFIELDS.h"
35 cnh 1.13
36     C !INPUT/OUTPUT PARAMETERS:
37 cnh 1.1 C == Routine arguments ==
38     C iMin - Working range of tile for applying forcing.
39     C iMax
40     C jMin
41     C jMax
42     C kLev
43     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
44 adcroft 1.4 _RL myCurrentTime
45     INTEGER myThid
46 cnh 1.1
47 cnh 1.13 C !LOCAL VARIABLES:
48 cnh 1.2 C == Local variables ==
49     C Loop counters
50     INTEGER I, J
51 mlosch 1.17 C number of surface interface layer
52     INTEGER kSurface
53 cnh 1.13 CEOP
54 cnh 1.2
55 jmc 1.21 if ( buoyancyRelation .eq. 'AMTMOSPHERIC' ) then
56     kSurface = 0
57     elseif ( buoyancyRelation .eq. 'OCEANICP' ) then
58 mlosch 1.17 kSurface = Nr
59     else
60     kSurface = 1
61     endif
62    
63 cnh 1.2 C-- Forcing term
64 jmc 1.21 #ifdef ALLOW_AIM
65     IF ( useAIM ) CALL AIM_TENDENCY_APPLY_U(
66     & iMin,iMax, jMin,jMax, bi,bj, kLev,
67     & myCurrentTime, myThid )
68     #endif /* ALLOW_AIM */
69    
70 cnh 1.2 C Add windstress momentum impulse into the top-layer
71 mlosch 1.17 IF ( kLev .EQ. kSurface ) THEN
72 cnh 1.2 DO j=jMin,jMax
73     DO i=iMin,iMax
74     gU(i,j,kLev,bi,bj) = gU(i,j,kLev,bi,bj)
75 heimbach 1.7 & +foFacMom*surfaceTendencyU(i,j,bi,bj)
76 adcroft 1.3 & *_maskW(i,j,kLev,bi,bj)
77 cnh 1.2 ENDDO
78     ENDDO
79     ENDIF
80    
81 heimbach 1.16 #if (defined (ALLOW_OBCS) && defined (ALLOW_OBCS_SPONGE))
82     IF (useOBCS) THEN
83     CALL OBCS_SPONGE_U(
84     I iMin, iMax, jMin, jMax,bi,bj,kLev,
85     I myCurrentTime,myThid)
86     ENDIF
87 heimbach 1.14 #endif
88    
89 cnh 1.1 RETURN
90     END
91 cnh 1.13 CBOP
92     C !ROUTINE: EXTERNAL_FORCING_V
93     C !INTERFACE:
94 cnh 1.1 SUBROUTINE EXTERNAL_FORCING_V(
95     I iMin, iMax, jMin, jMax,bi,bj,kLev,
96     I myCurrentTime,myThid)
97 cnh 1.13 C !DESCRIPTION: \bv
98     C *==========================================================*
99     C | S/R EXTERNAL_FORCING_V
100     C | o Contains problem specific forcing for merid velocity.
101     C *==========================================================*
102     C | Adds terms to gV for forcing by external sources
103     C | e.g. wind stress, bottom friction etc..................
104     C *==========================================================*
105     C \ev
106    
107     C !USES:
108 cnh 1.2 IMPLICIT NONE
109 cnh 1.1 C == Global data ==
110     #include "SIZE.h"
111     #include "EEPARAMS.h"
112     #include "PARAMS.h"
113     #include "GRID.h"
114     #include "DYNVARS.h"
115 cnh 1.2 #include "FFIELDS.h"
116    
117 cnh 1.13 C !INPUT/OUTPUT PARAMETERS:
118 cnh 1.1 C == Routine arguments ==
119     C iMin - Working range of tile for applying forcing.
120     C iMax
121     C jMin
122     C jMax
123     C kLev
124     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
125 adcroft 1.4 _RL myCurrentTime
126     INTEGER myThid
127 cnh 1.13
128     C !LOCAL VARIABLES:
129 cnh 1.2 C == Local variables ==
130     C Loop counters
131     INTEGER I, J
132 mlosch 1.17 C number of surface interface layer
133     INTEGER kSurface
134 cnh 1.13 CEOP
135 cnh 1.2
136 jmc 1.21 if ( buoyancyRelation .eq. 'AMTMOSPHERIC' ) then
137     kSurface = 0
138     elseif ( buoyancyRelation .eq. 'OCEANICP' ) then
139 mlosch 1.17 kSurface = Nr
140     else
141     kSurface = 1
142     endif
143    
144 cnh 1.2 C-- Forcing term
145 jmc 1.21 #ifdef ALLOW_AIM
146     IF ( useAIM ) CALL AIM_TENDENCY_APPLY_V(
147     & iMin,iMax, jMin,jMax, bi,bj, kLev,
148     & myCurrentTime, myThid )
149     #endif /* ALLOW_AIM */
150    
151 cnh 1.2 C Add windstress momentum impulse into the top-layer
152 mlosch 1.17 IF ( kLev .EQ. kSurface ) THEN
153 cnh 1.2 DO j=jMin,jMax
154     DO i=iMin,iMax
155     gV(i,j,kLev,bi,bj) = gV(i,j,kLev,bi,bj)
156 heimbach 1.7 & +foFacMom*surfaceTendencyV(i,j,bi,bj)
157 adcroft 1.3 & *_maskS(i,j,kLev,bi,bj)
158 cnh 1.2 ENDDO
159     ENDDO
160     ENDIF
161 cnh 1.1
162 heimbach 1.16 #if (defined (ALLOW_OBCS) && defined (ALLOW_OBCS_SPONGE))
163     IF (useOBCS) THEN
164     CALL OBCS_SPONGE_V(
165     I iMin, iMax, jMin, jMax,bi,bj,kLev,
166     I myCurrentTime,myThid)
167     ENDIF
168 heimbach 1.14 #endif
169    
170 cnh 1.1 RETURN
171     END
172 cnh 1.13 CBOP
173     C !ROUTINE: EXTERNAL_FORCING_T
174     C !INTERFACE:
175 cnh 1.1 SUBROUTINE EXTERNAL_FORCING_T(
176     I iMin, iMax, jMin, jMax,bi,bj,kLev,
177     I myCurrentTime,myThid)
178 cnh 1.13 C !DESCRIPTION: \bv
179     C *==========================================================*
180     C | S/R EXTERNAL_FORCING_T
181     C | o Contains problem specific forcing for temperature.
182     C *==========================================================*
183     C | Adds terms to gT for forcing by external sources
184     C | e.g. heat flux, climatalogical relaxation..............
185     C *==========================================================*
186     C \ev
187    
188     C !USES:
189 cnh 1.2 IMPLICIT NONE
190 cnh 1.1 C == Global data ==
191     #include "SIZE.h"
192     #include "EEPARAMS.h"
193     #include "PARAMS.h"
194     #include "GRID.h"
195     #include "DYNVARS.h"
196     #include "FFIELDS.h"
197 heimbach 1.7 #ifdef SHORTWAVE_HEATING
198 heimbach 1.8 integer two
199     _RL minusone
200     parameter (two=2,minusone=-1.)
201     _RL swfracb(two)
202 heimbach 1.7 #endif
203    
204 cnh 1.13 C !INPUT/OUTPUT PARAMETERS:
205 cnh 1.1 C == Routine arguments ==
206     C iMin - Working range of tile for applying forcing.
207     C iMax
208     C jMin
209     C jMax
210     C kLev
211     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
212 adcroft 1.4 _RL myCurrentTime
213     INTEGER myThid
214 cnh 1.1 CEndOfInterface
215    
216 cnh 1.13 C !LOCAL VARIABLES:
217 cnh 1.2 C == Local variables ==
218     C Loop counters
219     INTEGER I, J
220 mlosch 1.17 C number of surface interface layer
221     INTEGER kSurface
222 cnh 1.13 CEOP
223 cnh 1.2
224 jmc 1.21 if ( buoyancyRelation .eq. 'AMTMOSPHERIC' ) then
225     kSurface = 0
226     elseif ( buoyancyRelation .eq. 'OCEANICP' ) then
227 mlosch 1.17 kSurface = Nr
228     else
229     kSurface = 1
230     endif
231    
232 cnh 1.2 C-- Forcing term
233 jmc 1.21 #ifdef ALLOW_AIM
234     IF ( useAIM ) CALL AIM_TENDENCY_APPLY_T(
235     & iMin,iMax, jMin,jMax, bi,bj, kLev,
236     & myCurrentTime, myThid )
237     #endif /* ALLOW_AIM */
238    
239 cnh 1.2 C Add heat in top-layer
240 mlosch 1.17 IF ( kLev .EQ. kSurface ) THEN
241 cnh 1.2 DO j=jMin,jMax
242     DO i=iMin,iMax
243     gT(i,j,kLev,bi,bj)=gT(i,j,kLev,bi,bj)
244 adcroft 1.12 & +maskC(i,j,kLev,bi,bj)*surfaceTendencyT(i,j,bi,bj)
245 cnh 1.2 ENDDO
246     ENDDO
247     ENDIF
248 adcroft 1.5
249     #ifdef SHORTWAVE_HEATING
250     C Penetrating SW radiation
251 heimbach 1.8 swfracb(1)=abs(rF(klev))
252     swfracb(2)=abs(rF(klev+1))
253     call SWFRAC(
254     I two,minusone,
255     I myCurrentTime,myThid,
256 dimitri 1.18 U swfracb)
257 adcroft 1.5 DO j=jMin,jMax
258     DO i=iMin,iMax
259 adcroft 1.12 gT(i,j,klev,bi,bj) = gT(i,j,klev,bi,bj)
260     & -maskC(i,j,klev,bi,bj)*Qsw(i,j,bi,bj)*(swfracb(1)-swfracb(2))
261 mlosch 1.17 & *recip_Cp*recip_rhoConst*recip_drF(klev)
262 adcroft 1.5 ENDDO
263     ENDDO
264     #endif
265 heimbach 1.14
266 heimbach 1.16 #if (defined (ALLOW_OBCS) && defined (ALLOW_OBCS_SPONGE))
267     IF (useOBCS) THEN
268     CALL OBCS_SPONGE_T(
269     I iMin, iMax, jMin, jMax,bi,bj,kLev,
270     I myCurrentTime,myThid)
271     ENDIF
272 heimbach 1.14 #endif
273    
274 cnh 1.1 RETURN
275     END
276 cnh 1.13 CBOP
277     C !ROUTINE: EXTERNAL_FORCING_S
278     C !INTERFACE:
279 cnh 1.1 SUBROUTINE EXTERNAL_FORCING_S(
280     I iMin, iMax, jMin, jMax,bi,bj,kLev,
281     I myCurrentTime,myThid)
282 cnh 1.13
283     C !DESCRIPTION: \bv
284     C *==========================================================*
285     C | S/R EXTERNAL_FORCING_S
286     C | o Contains problem specific forcing for merid velocity.
287     C *==========================================================*
288     C | Adds terms to gS for forcing by external sources
289     C | e.g. fresh-water flux, climatalogical relaxation.......
290     C *==========================================================*
291     C \ev
292    
293     C !USES:
294 cnh 1.2 IMPLICIT NONE
295 cnh 1.1 C == Global data ==
296     #include "SIZE.h"
297     #include "EEPARAMS.h"
298     #include "PARAMS.h"
299     #include "GRID.h"
300     #include "DYNVARS.h"
301 cnh 1.2 #include "FFIELDS.h"
302 cnh 1.1
303 cnh 1.13 C !INPUT/OUTPUT PARAMETERS:
304 cnh 1.1 C == Routine arguments ==
305     C iMin - Working range of tile for applying forcing.
306     C iMax
307     C jMin
308     C jMax
309     C kLev
310     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
311 adcroft 1.4 _RL myCurrentTime
312     INTEGER myThid
313 cnh 1.2
314 cnh 1.13 C !LOCAL VARIABLES:
315 cnh 1.2 C == Local variables ==
316     C Loop counters
317     INTEGER I, J
318 mlosch 1.17 C number of surface interface layer
319     INTEGER kSurface
320 cnh 1.13 CEOP
321 cnh 1.2
322 jmc 1.21 if ( buoyancyRelation .eq. 'AMTMOSPHERIC' ) then
323     kSurface = 0
324     elseif ( buoyancyRelation .eq. 'OCEANICP' ) then
325 mlosch 1.17 kSurface = Nr
326     else
327     kSurface = 1
328     endif
329    
330    
331 cnh 1.2 C-- Forcing term
332 jmc 1.21 #ifdef ALLOW_AIM
333     IF ( useAIM ) CALL AIM_TENDENCY_APPLY_S(
334     & iMin,iMax, jMin,jMax, bi,bj, kLev,
335     & myCurrentTime, myThid )
336     #endif /* ALLOW_AIM */
337    
338 cnh 1.2 C Add fresh-water in top-layer
339 mlosch 1.17 IF ( kLev .EQ. kSurface ) THEN
340 cnh 1.2 DO j=jMin,jMax
341     DO i=iMin,iMax
342     gS(i,j,kLev,bi,bj)=gS(i,j,kLev,bi,bj)
343 adcroft 1.12 & +maskC(i,j,kLev,bi,bj)*surfaceTendencyS(i,j,bi,bj)
344 cnh 1.2 ENDDO
345     ENDDO
346     ENDIF
347 heimbach 1.14
348 heimbach 1.16 #if (defined (ALLOW_OBCS) && defined (ALLOW_OBCS_SPONGE))
349     IF (useOBCS) THEN
350     CALL OBCS_SPONGE_S(
351     I iMin, iMax, jMin, jMax,bi,bj,kLev,
352     I myCurrentTime,myThid)
353     ENDIF
354 heimbach 1.14 #endif
355 cnh 1.1
356     RETURN
357     END

  ViewVC Help
Powered by ViewVC 1.1.22