/[MITgcm]/MITgcm/verification/hs94.1x64x5/code/external_forcing.F
ViewVC logotype

Annotation of /MITgcm/verification/hs94.1x64x5/code/external_forcing.F

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


Revision 1.3 - (hide annotations) (download)
Sun Feb 4 14:38:53 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint38, c37_adj, checkpoint39, checkpoint37, checkpoint36, checkpoint35
Branch point for: pre38
Changes since 1.2: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

1 cnh 1.3 C $Header: /u/gcmpack/models/MITgcmUV/verification/hs94.1x64x5/code/external_forcing.F,v 1.2 2001/02/02 21:36:34 adcroft Exp $
2     C $Name: $
3 adcroft 1.2
4     #include "CPP_OPTIONS.h"
5    
6     CStartOfInterface
7     SUBROUTINE EXTERNAL_FORCING_U(
8     I iMin, iMax, jMin, jMax,bi,bj,kLev,
9     I myCurrentTime,myThid)
10     C /==========================================================\
11     C | S/R EXTERNAL_FORCING_U |
12     C | o Contains problem specific forcing for zonal velocity. |
13     C |==========================================================|
14     C | Adds terms to gU for forcing by external sources |
15     C | e.g. wind stress, bottom friction etc.................. |
16     C \==========================================================/
17    
18     C == Global data ==
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "GRID.h"
23     #include "DYNVARS.h"
24     #include "FFIELDS.h"
25    
26     #ifdef USE_FRANCO_PHYSICS
27     #include "atparam0.h"
28     #include "atparam1.h"
29     INTEGER NGP
30     INTEGER NLON
31     INTEGER NLAT
32     INTEGER NLEV
33     PARAMETER ( NLON=IX, NLAT=IL, NLEV=KX, NGP=NLON*NLAT )
34     #include "com_physvar.h"
35     #define _KDKA( KD ) Nr-KD+1
36     #endif
37    
38     C == Routine arguments ==
39     C iMin - Working range of tile for applying forcing.
40     C iMax
41     C jMin
42     C jMax
43     C kLev
44     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
45     _RL myCurrentTime
46     INTEGER myThid
47     CEndOfInterface
48    
49     C == Local variables ==
50     C Loop counters
51     INTEGER I, J
52     C _RL uKf
53     C _RL levelOfGround
54     C _RL criticalLevel
55     C _RL levelOfVelPoint
56     C _RL dist1
57     C _RL dist2
58     C _RL decayFac
59     C _RL velDragHeightFac
60     _RL termP,kV,kF
61    
62     C-- Forcing term(s)
63     kF=1./86400.
64     DO J=jMin,jMax
65     DO I=iMin,iMax
66     IF ( HFacW(i,j,kLev,bi,bj) .GT. 0. ) THEN
67     termP=0.5*( rF(kLev) + rF(kLev+1) )
68     kV=kF*MAX(0., (termP*recip_H(I,J,bi,bj)-0.7)/(1.-0.7) )
69     gU(i,j,kLev,bi,bj)=gU(i,j,kLev,bi,bj)
70     & -kV*uVel(i,j,kLev,bi,bj)
71     ENDIF
72     ENDDO
73     ENDDO
74    
75     RETURN
76     END
77     CStartOfInterface
78     SUBROUTINE EXTERNAL_FORCING_V(
79     I iMin, iMax, jMin, jMax,bi,bj,kLev,
80     I myCurrentTime,myThid)
81     C /==========================================================\
82     C | S/R EXTERNAL_FORCING_V |
83     C | o Contains problem specific forcing for merid velocity. |
84     C |==========================================================|
85     C | Adds terms to gV for forcing by external sources |
86     C | e.g. wind stress, bottom friction etc.................. |
87     C \==========================================================/
88     IMPLICIT NONE
89    
90     C == Global data ==
91     #include "SIZE.h"
92     #include "EEPARAMS.h"
93     #include "PARAMS.h"
94     #include "GRID.h"
95     #include "DYNVARS.h"
96     #include "FFIELDS.h"
97    
98    
99     C == Routine arguments ==
100     C iMin - Working range of tile for applying forcing.
101     C iMax
102     C jMin
103     C jMax
104     C kLev
105     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
106     _RL myCurrentTime
107     INTEGER myThid
108     CEndOfInterface
109     C == Local variables ==
110     C Loop counters
111     INTEGER I, J
112     C _RL uKf
113     C _RL levelOfGround
114     C _RL criticalLevel
115     C _RL levelOfVelPoint
116     C _RL dist1
117     C _RL dist2
118     C _RL decayFac
119     C _RL velDragHeightFac
120     _RL termP,kV,kF
121    
122     C-- Forcing term(s)
123     kF=1./86400.
124     DO J=jMin,jMax
125     DO I=iMin,iMax
126     IF ( HFacS(i,j,kLev,bi,bj) .GT. 0. ) THEN
127     termP=0.5*( rF(kLev) + rF(kLev+1) )
128     kV=kF*MAX(0., (termP*recip_H(I,J,bi,bj)-0.7)/(1.-0.7) )
129     gV(i,j,kLev,bi,bj)=gV(i,j,kLev,bi,bj)
130     & -kV*vVel(i,j,kLev,bi,bj)
131     ENDIF
132     ENDDO
133     ENDDO
134    
135     RETURN
136     END
137    
138     CStartOfInterface
139     SUBROUTINE EXTERNAL_FORCING_T(
140     I iMin, iMax, jMin, jMax,bi,bj,kLev,
141     I maskC,
142     I myCurrentTime,myThid)
143     C /==========================================================\
144     C | S/R EXTERNAL_FORCING_T |
145     C | o Contains problem specific forcing for temperature. |
146     C |==========================================================|
147     C | Adds terms to gT for forcing by external sources |
148     C | e.g. heat flux, climatalogical relaxation.............. |
149     C \==========================================================/
150     IMPLICIT NONE
151    
152     C == Global data ==
153     #include "SIZE.h"
154     #include "EEPARAMS.h"
155     #include "PARAMS.h"
156     #include "GRID.h"
157     #include "DYNVARS.h"
158     #include "FFIELDS.h"
159    
160     #ifdef USE_FRANCO_PHYSICS
161     #include "atparam0.h"
162     #include "atparam1.h"
163     INTEGER NGP
164     INTEGER NLON
165     INTEGER NLAT
166     INTEGER NLEV
167     PARAMETER ( NLON=IX, NLAT=IL, NLEV=KX, NGP=NLON*NLAT )
168     #include "com_physvar.h"
169     #define _KDKA( KD ) Nr-KD+1
170     #endif
171    
172     C == Routine arguments ==
173     C iMin - Working range of tile for applying forcing.
174     C iMax
175     C jMin
176     C jMax
177     C kLev
178     _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
179     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
180     _RL myCurrentTime
181     INTEGER myThid
182     CEndOfInterface
183    
184     C == Local variables ==
185     C Loop counters
186     INTEGER I, J
187     _RL thetaLim,kT,ka,ks,term1,term2,thetaEq,termP,rSurf
188    
189     C-- Forcing term(s)
190     rSurf=1.E5
191     ka=1./(40.*86400.)
192     ks=1./(4. *86400.)
193     DO J=jMin,jMax
194     term1=60.*(sin(yC(1,J,bi,bj)*deg2rad)**2)
195     C termP=0.5*( rF(kLev) + min( rF(kLev+1) , H(I,J,bi,bj) ) )
196     termP=0.5*( rF(kLev) + rF(kLev+1) )
197     C termP=rC(kLev)
198     term2=10.*log(termP/rSurf)
199     & *(cos(yC(1,J,bi,bj)*deg2rad)**2)
200     thetaLim = 200. / ((termP/rSurf)**(2./7.))
201     C thetaLim = 170. / ((termP/rSurf)**(2./7.))
202     thetaEq=315.-term1-term2
203     thetaEq=MAX(thetaLim,thetaEq)
204     DO I=iMin,iMax
205     kT=ka+(ks-ka)
206     & *MAX(0., (termP*recip_H(I,J,bi,bj)-0.7)/(1.-0.7) )
207     & *COS((yC(1,J,bi,bj)*deg2rad))**4
208     gT(i,j,kLev,bi,bj)=gT(i,j,kLev,bi,bj)
209     & - kT*( theta(I,J,kLev,bi,bj)-thetaEq )
210     & *maskC(i,j)
211     ENDDO
212     ENDDO
213    
214     RETURN
215     END
216    
217     CStartOfInterface
218     SUBROUTINE EXTERNAL_FORCING_S(
219     I iMin, iMax, jMin, jMax,bi,bj,kLev,
220     I maskC,
221     I myCurrentTime,myThid)
222     C /==========================================================\
223     C | S/R EXTERNAL_FORCING_S |
224     C | o Contains problem specific forcing for merid velocity. |
225     C |==========================================================|
226     C | Adds terms to gS for forcing by external sources |
227     C | e.g. fresh-water flux, climatalogical relaxation....... |
228     C \==========================================================/
229     IMPLICIT NONE
230    
231     C == Global data ==
232     #include "SIZE.h"
233     #include "EEPARAMS.h"
234     #include "PARAMS.h"
235     #include "GRID.h"
236     #include "DYNVARS.h"
237     #include "FFIELDS.h"
238    
239     #ifdef USE_FRANCO_PHYSICS
240     #include "atparam0.h"
241     #include "atparam1.h"
242     INTEGER NGP
243     INTEGER NLON
244     INTEGER NLAT
245     INTEGER NLEV
246     PARAMETER ( NLON=IX, NLAT=IL, NLEV=KX, NGP=NLON*NLAT )
247     #include "com_physvar.h"
248     #define _KDKA( KD ) Nr-KD+1
249     #endif
250    
251     C == Routine arguments ==
252     C iMin - Working range of tile for applying forcing.
253     C iMax
254     C jMin
255     C jMax
256     C kLev
257     _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
258     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
259     _RL myCurrentTime
260     INTEGER myThid
261     CEndOfInterface
262    
263     C == Local variables ==
264     C Loop counters
265    
266     C-- Forcing term
267    
268     RETURN
269     END

  ViewVC Help
Powered by ViewVC 1.1.22