/[MITgcm]/MITgcm_contrib/dgoldberg/shelfice/shelfice_forcing.F
ViewVC logotype

Contents of /MITgcm_contrib/dgoldberg/shelfice/shelfice_forcing.F

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


Revision 1.1 - (show annotations) (download)
Tue Apr 21 11:07:10 2015 UTC (10 years, 2 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
revert to non-shelficeboundary layer behavior if hfacC(ktopC)>1

1 C $Header: /u/gcmpack/MITgcm/pkg/shelfice/shelfice_forcing.F,v 1.5 2014/07/09 17:00:50 jmc Exp $
2 C $Name: $
3
4 #include "SHELFICE_OPTIONS.h"
5
6 C-- File shelfice_forcing.F:
7 C-- Contents
8 C-- o SHELFICE_FORCING_T
9 C-- o SHELFICE_FORCING_S
10
11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 CBOP
13 C !ROUTINE: SHELFICE_FORCING_T
14 C !INTERFACE:
15 SUBROUTINE SHELFICE_FORCING_T(
16 U gT_arr,
17 I iMin,iMax,jMin,jMax, kLev, bi, bj,
18 I myTime, myIter, myThid )
19
20 C !DESCRIPTION: \bv
21 C *==========================================================*
22 C | S/R SHELFICE_FORCING_T
23 C | o Contains problem specific forcing for temperature.
24 C *==========================================================*
25 C | Adds terms to gT for forcing by shelfice sources
26 C | e.g. heat flux
27 C *==========================================================*
28 C \ev
29
30 C !USES:
31 IMPLICIT NONE
32 C == Global data ==
33 #include "SIZE.h"
34 #include "EEPARAMS.h"
35 #include "PARAMS.h"
36 #include "GRID.h"
37 c#include "DYNVARS.h"
38 c#include "FFIELDS.h"
39 #include "SHELFICE.h"
40
41 C !INPUT/OUTPUT PARAMETERS:
42 C gT_arr :: the tendency array
43 C iMin,iMax :: Working range of x-index for applying forcing.
44 C jMin,jMax :: Working range of y-index for applying forcing.
45 C kLev :: Current vertical level index
46 C bi,bj :: Current tile indices
47 C myTime :: Current time in simulation
48 C myIter :: Current iteration number
49 C myThid :: my Thread Id number
50 _RL gT_arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 INTEGER iMin, iMax, jMin, jMax
52 INTEGER kLev, bi, bj
53 _RL myTime
54 INTEGER myIter
55 INTEGER myThid
56
57 #ifdef ALLOW_SHELFICE
58 C !LOCAL VARIABLES:
59 C == Local variables ==
60 C i,j :: Loop counters
61 C kp1,km1 :: index of next/previous level
62 C gTloc :: local tendency in boundary layer
63 C drLoc :: fractional cell width of boundary layer in (k+/-1)th layer
64 INTEGER i, j
65 INTEGER Kp1, Km1
66 _RS drLoc
67 _RL gTloc
68 CEOP
69
70 C-- Forcing term
71 IF ( SHELFICEboundaryLayer ) THEN
72 DO j=1,sNy
73 DO i=1,sNx
74 IF ( kLev .LT. Nr .AND. kLev .EQ. kTopC(I,J,bi,bj) ) THEN
75 kp1 = MIN(kLev+1,Nr)
76 drLoc = drF(kLev)*( 1. _d 0 - _hFacC(I,J,kLev,bi,bj) )
77 drLoc = MIN( drLoc, drF(Kp1) * _hFacC(I,J,Kp1,bi,bj) )
78 drLoc = MAX( drLoc, 0. _d 0)
79 gTloc = shelficeForcingT(i,j,bi,bj)
80 & /( drF(kLev)*_hFacC(I,J,kLev,bi,bj)+drLoc )
81 gT_arr(i,j) = gT_arr(i,j) + gTloc
82 ELSEIF ( kLev .GT. 1 .AND. kLev-1 .EQ. kTopC(I,J,bi,bj) ) THEN
83 km1 = MAX(kLev-1,1)
84 drLoc = drF(km1)*( 1. _d 0 - _hFacC(I,J,km1,bi,bj) )
85 drLoc = MIN( drLoc, drF(kLev) * _hFacC(I,J,kLev,bi,bj) )
86 drLoc = MAX( drLoc, 0. _d 0)
87 gTloc = shelficeForcingT(i,j,bi,bj)
88 & /( drF(km1)*_hFacC(I,J,km1,bi,bj)+drLoc )
89 C The following is shorthand for the averaged tendency:
90 C gT(k+1) = gT(k+1) + { gTloc * [drF(k)*(1-hFacC(k))]
91 C + 0 * [drF(k+1) - drF(k)*(1-hFacC(k))]
92 C }/[drF(k+1)*hFacC(k+1)]
93 gT_arr(i,j) = gT_arr(i,j) + gTloc
94 & * drLoc*recip_drF(kLev)* _recip_hFacC(i,j,kLev,bi,bj)
95 ENDIF
96 ENDDO
97 ENDDO
98 ENDIF
99
100 #endif /* ALLOW_SHELFICE */
101 RETURN
102 END
103
104 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
105 CBOP
106 C !ROUTINE: SHELFICE_FORCING_S
107 C !INTERFACE:
108 SUBROUTINE SHELFICE_FORCING_S(
109 U gS_arr,
110 I iMin,iMax,jMin,jMax, kLev, bi, bj,
111 I myTime, myIter, myThid )
112
113 C !DESCRIPTION: \bv
114 C *==========================================================*
115 C | S/R SHELFICE_FORCING_S
116 C | o Contains problem specific forcing for merid velocity.
117 C *==========================================================*
118 C | Adds terms to gS for forcing by shelfice sources
119 C | e.g. fresh-water flux (virtual salt flux).
120 C *==========================================================*
121 C \ev
122
123 C !USES:
124 IMPLICIT NONE
125 C == Global data ==
126 #include "SIZE.h"
127 #include "EEPARAMS.h"
128 #include "PARAMS.h"
129 #include "GRID.h"
130 c#include "DYNVARS.h"
131 c#include "FFIELDS.h"
132 #include "SHELFICE.h"
133
134 C !INPUT/OUTPUT PARAMETERS:
135 C gS_arr :: the tendency array
136 C iMin,iMax :: Working range of x-index for applying forcing.
137 C jMin,jMax :: Working range of y-index for applying forcing.
138 C kLev :: Current vertical level index
139 C bi,bj :: Current tile indices
140 C myTime :: Current time in simulation
141 C myIter :: Current iteration number
142 C myThid :: my Thread Id number
143 _RL gS_arr(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
144 INTEGER iMin, iMax, jMin, jMax
145 INTEGER kLev, bi, bj
146 _RL myTime
147 INTEGER myIter
148 INTEGER myThid
149
150 #ifdef ALLOW_SHELFICE
151 C !LOCAL VARIABLES:
152 C i,j :: Loop counters
153 C kp/m1 :: index of next/previous level
154 C gTloc :: local tendency in boundary layer
155 C drLoc :: fractional cell width of boundary layer
156 INTEGER i, j
157 INTEGER Kp1, Km1
158 _RS drLoc
159 _RL gSloc
160 CEOP
161
162 C-- Forcing term
163 IF ( SHELFICEboundaryLayer ) THEN
164 DO j=1,sNy
165 DO i=1,sNx
166 IF ( kLev .LT. Nr .AND. kLev .EQ. kTopC(I,J,bi,bj) ) THEN
167 kp1 = MIN(kLev+1,Nr)
168 drLoc = drF(kLev)*( 1. _d 0 - _hFacC(I,J,kLev,bi,bj) )
169 drLoc = MIN( drLoc, drF(Kp1) * _hFacC(I,J,Kp1,bi,bj) )
170 drLoc = MAX( drLoc, 0. _d 0)
171 gSloc = shelficeForcingS(i,j,bi,bj)
172 & /( drF(kLev)*_hFacC(I,J,kLev,bi,bj)+drLoc )
173 gS_arr(i,j) = gS_arr(i,j) + gSloc
174 ELSEIF ( kLev .GT. 1 .AND. kLev-1 .EQ. kTopC(I,J,bi,bj) ) THEN
175 km1 = MAX(kLev-1,1)
176 drLoc = drF(km1)*( 1. _d 0 - _hFacC(I,J,km1,bi,bj) )
177 drLoc = MIN( drLoc, drF(kLev) * _hFacC(I,J,kLev,bi,bj) )
178 drLoc = MAX( drLoc, 0. _d 0)
179 gSloc = shelficeForcingS(i,j,bi,bj)
180 & /( drF(km1)*_hFacC(I,J,km1,bi,bj)+drLoc )
181 C The following is shorthand for the averaged tendency:
182 C gS(k+1) = gS(k+1) + { gSloc * [drF(k)*(1-hFacC(k))]
183 C + 0 * [drF(k+1) - drF(k)*(1-hFacC(k))]
184 C }/[drF(k+1)*hFacC(k+1)]
185 gS_arr(i,j) = gS_arr(i,j) + gSloc
186 & * drLoc*recip_drF(kLev)* _recip_hFacC(i,j,kLev,bi,bj)
187 ENDIF
188 ENDDO
189 ENDDO
190 ENDIF
191
192 #endif /* ALLOW_SHELFICE */
193 RETURN
194 END

  ViewVC Help
Powered by ViewVC 1.1.22