/[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.5 - (hide annotations) (download)
Tue May 18 18:01:13 1999 UTC (25 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint22, checkpoint23
Changes since 1.4: +12 -1 lines
Modifications/additions for KPP mixing scheme. Instigated by Dimitri.

1 adcroft 1.5 C $Header: /u/gcmpack/models/MITgcmUV/model/src/external_forcing.F,v 1.4 1999/05/05 14:52:49 adcroft Exp $
2 cnh 1.1
3     #include "CPP_OPTIONS.h"
4    
5     CStartOfInterface
6     SUBROUTINE EXTERNAL_FORCING_U(
7     I iMin, iMax, jMin, jMax,bi,bj,kLev,
8     I myCurrentTime,myThid)
9     C /==========================================================\
10     C | S/R EXTERNAL_FORCING_U |
11     C | o Contains problem specific forcing for zonal velocity. |
12     C |==========================================================|
13     C | Adds terms to gU for forcing by external sources |
14     C | e.g. wind stress, bottom friction etc.................. |
15     C \==========================================================/
16 cnh 1.2 IMPLICIT NONE
17 cnh 1.1
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 cnh 1.2 #include "FFIELDS.h"
25 cnh 1.1
26     C == Routine arguments ==
27     C iMin - Working range of tile for applying forcing.
28     C iMax
29     C jMin
30     C jMax
31     C kLev
32     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
33 adcroft 1.4 _RL myCurrentTime
34     INTEGER myThid
35 cnh 1.1 CEndOfInterface
36    
37 cnh 1.2 C == Local variables ==
38     C Loop counters
39     INTEGER I, J
40    
41     C-- Forcing term
42     C Add windstress momentum impulse into the top-layer
43     IF ( kLev .EQ. 1 ) THEN
44     DO j=jMin,jMax
45     DO i=iMin,iMax
46     gU(i,j,kLev,bi,bj) = gU(i,j,kLev,bi,bj)
47 adcroft 1.3 & +foFacMom*fu(i,j,bi,bj)
48     & *horiVertRatio*recip_rhoNil*recip_dRf(kLev)
49     & *_maskW(i,j,kLev,bi,bj)
50 cnh 1.2 ENDDO
51     ENDDO
52     ENDIF
53    
54 cnh 1.1 RETURN
55     END
56     CStartOfInterface
57     SUBROUTINE EXTERNAL_FORCING_V(
58     I iMin, iMax, jMin, jMax,bi,bj,kLev,
59     I myCurrentTime,myThid)
60     C /==========================================================\
61     C | S/R EXTERNAL_FORCING_V |
62     C | o Contains problem specific forcing for merid velocity. |
63     C |==========================================================|
64     C | Adds terms to gV for forcing by external sources |
65     C | e.g. wind stress, bottom friction etc.................. |
66     C \==========================================================/
67 cnh 1.2 IMPLICIT NONE
68 cnh 1.1
69     C == Global data ==
70     #include "SIZE.h"
71     #include "EEPARAMS.h"
72     #include "PARAMS.h"
73     #include "GRID.h"
74     #include "DYNVARS.h"
75 cnh 1.2 #include "FFIELDS.h"
76    
77 cnh 1.1
78     C == Routine arguments ==
79     C iMin - Working range of tile for applying forcing.
80     C iMax
81     C jMin
82     C jMax
83     C kLev
84     INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
85 adcroft 1.4 _RL myCurrentTime
86     INTEGER myThid
87 cnh 1.1 CEndOfInterface
88 cnh 1.2 C == Local variables ==
89     C Loop counters
90     INTEGER I, J
91    
92     C-- Forcing term
93     C Add windstress momentum impulse into the top-layer
94     IF ( kLev .EQ. 1 ) THEN
95     DO j=jMin,jMax
96     DO i=iMin,iMax
97     gV(i,j,kLev,bi,bj) = gV(i,j,kLev,bi,bj)
98 adcroft 1.3 & +foFacMom*fv(i,j,bi,bj)
99     & *horiVertRatio*recip_rhoNil*recip_dRf(kLev)
100     & *_maskS(i,j,kLev,bi,bj)
101 cnh 1.2 ENDDO
102     ENDDO
103     ENDIF
104 cnh 1.1
105     RETURN
106     END
107     CStartOfInterface
108     SUBROUTINE EXTERNAL_FORCING_T(
109     I iMin, iMax, jMin, jMax,bi,bj,kLev,
110 cnh 1.2 I maskC,
111 cnh 1.1 I myCurrentTime,myThid)
112     C /==========================================================\
113     C | S/R EXTERNAL_FORCING_T |
114     C | o Contains problem specific forcing for temperature. |
115     C |==========================================================|
116     C | Adds terms to gT for forcing by external sources |
117     C | e.g. heat flux, climatalogical relaxation.............. |
118     C \==========================================================/
119 cnh 1.2 IMPLICIT NONE
120 cnh 1.1
121     C == Global data ==
122     #include "SIZE.h"
123     #include "EEPARAMS.h"
124     #include "PARAMS.h"
125     #include "GRID.h"
126     #include "DYNVARS.h"
127     #include "FFIELDS.h"
128    
129     C == Routine arguments ==
130     C iMin - Working range of tile for applying forcing.
131     C iMax
132     C jMin
133     C jMax
134     C kLev
135 cnh 1.2 _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
136 cnh 1.1 INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
137 adcroft 1.4 _RL myCurrentTime
138     INTEGER myThid
139 cnh 1.1 CEndOfInterface
140    
141 cnh 1.2 C == Local variables ==
142     C Loop counters
143     INTEGER I, J
144    
145     C-- Forcing term
146     C Add heat in top-layer
147     IF ( kLev .EQ. 1 ) THEN
148     DO j=jMin,jMax
149     DO i=iMin,iMax
150     gT(i,j,kLev,bi,bj)=gT(i,j,kLev,bi,bj)
151     & +maskC(i,j)*(
152     & -lambdaThetaClimRelax*(theta(i,j,kLev,bi,bj)-SST(i,j,bi,bj))
153 adcroft 1.3 & -Qnet(i,j,bi,bj)*recip_Cp*recip_rhoNil*recip_dRf(kLev) )
154 cnh 1.2 ENDDO
155     ENDDO
156     ENDIF
157 adcroft 1.5
158     #ifdef SHORTWAVE_HEATING
159     C Penetrating SW radiation
160     DO j=jMin,jMax
161     DO i=iMin,iMax
162     gT(i,j,k,bi,bj) = gT(i,j,k,bi,bj)
163     & - maskC(i,j)*Qsw(i,j,bi,bj)*swfracb(k)
164     & *recip_Cp*recip_rhoNil*recip_dRf(k)
165     ENDDO
166     ENDDO
167     #endif
168 cnh 1.2
169 cnh 1.1 RETURN
170     END
171     CStartOfInterface
172     SUBROUTINE EXTERNAL_FORCING_S(
173     I iMin, iMax, jMin, jMax,bi,bj,kLev,
174 cnh 1.2 I maskC,
175 cnh 1.1 I myCurrentTime,myThid)
176     C /==========================================================\
177     C | S/R EXTERNAL_FORCING_S |
178     C | o Contains problem specific forcing for merid velocity. |
179     C |==========================================================|
180     C | Adds terms to gS for forcing by external sources |
181     C | e.g. fresh-water flux, climatalogical relaxation....... |
182     C \==========================================================/
183 cnh 1.2 IMPLICIT NONE
184 cnh 1.1
185     C == Global data ==
186     #include "SIZE.h"
187     #include "EEPARAMS.h"
188     #include "PARAMS.h"
189     #include "GRID.h"
190     #include "DYNVARS.h"
191 cnh 1.2 #include "FFIELDS.h"
192 cnh 1.1
193     C == Routine arguments ==
194     C iMin - Working range of tile for applying forcing.
195     C iMax
196     C jMin
197     C jMax
198     C kLev
199 cnh 1.2 _RS maskC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
200 cnh 1.1 INTEGER iMin, iMax, jMin, jMax, kLev, bi, bj
201 adcroft 1.4 _RL myCurrentTime
202     INTEGER myThid
203 cnh 1.1 CEndOfInterface
204 cnh 1.2
205     C == Local variables ==
206     C Loop counters
207     INTEGER I, J
208    
209     C-- Forcing term
210     C Add fresh-water in top-layer
211     IF ( kLev .EQ. 1 ) THEN
212     DO j=jMin,jMax
213     DO i=iMin,iMax
214     gS(i,j,kLev,bi,bj)=gS(i,j,kLev,bi,bj)
215     & +maskC(i,j)*(
216     & -lambdaSaltClimRelax*(salt(i,j,kLev,bi,bj)-SSS(i,j,bi,bj))
217 adcroft 1.3 #ifndef USE_NATURAL_BCS
218     & +EmPmR(i,j,bi,bj)*recip_dRf(1)*35.
219     #endif
220     & )
221 cnh 1.2 ENDDO
222     ENDDO
223     ENDIF
224 cnh 1.1
225     RETURN
226     END

  ViewVC Help
Powered by ViewVC 1.1.22