/[MITgcm]/MITgcm/verification/tidal_basin_2d/code/external_forcing.F
ViewVC logotype

Annotation of /MITgcm/verification/tidal_basin_2d/code/external_forcing.F

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


Revision 1.4 - (hide annotations) (download)
Sun Jul 18 01:23:05 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint54e_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint57g_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint55, checkpoint57f_pre, checkpoint57a_post, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57h_done, checkpoint57f_post, checkpoint57c_post, checkpoint55e_post, checkpoint55a_post, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.3: +9 -7 lines
replace surfaceTendency U,V,S,T,Tice by surfaceForcing U,V,S,T,Tice

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

  ViewVC Help
Powered by ViewVC 1.1.22