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

Contents of /MITgcm/model/src/set_parms.F

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


Revision 1.26 - (show annotations) (download)
Wed Oct 4 20:34:23 2017 UTC (6 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, HEAD
Changes since 1.25: +8 -7 lines
add run-time param to allow to turn off tidal forcing.

1 C $Header: /u/gcmpack/MITgcm/model/src/set_parms.F,v 1.25 2016/03/10 20:52:06 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6 #ifdef ALLOW_MOM_COMMON
7 # include "MOM_COMMON_OPTIONS.h"
8 #endif
9
10 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
11 CBOP
12 C !ROUTINE: SET_PARMS
13 C !INTERFACE:
14 SUBROUTINE SET_PARMS( myThid )
15
16 C !DESCRIPTION:
17 C Set model "parameters" that might depend on the use of some pkgs;
18 C called from INITIALISE_FIXED, after INI_PARMS & PACKAGES_READPARAMS
19 C NOTES: After leaving this S/R, parameters will not change anymore.
20
21 C !USES:
22 IMPLICIT NONE
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "EOS.h"
27 #ifdef ALLOW_MOM_COMMON
28 # include "MOM_VISC.h"
29 #endif
30
31 C !INPUT/OUTPUT PARAMETERS:
32 C myThid :: My Thread Id number
33 INTEGER myThid
34
35 C !FUNCTIONS:
36 c INTEGER ILNBLNK
37 c EXTERNAL ILNBLNK
38
39 C !LOCAL VARIABLES:
40 CHARACTER*(MAX_LEN_MBUF) msgBuf
41 INTEGER k
42 _RL tmpVar
43 CEOP
44
45 C-- Set (or reset) On/Off flags :
46
47 C- For off-line calculation, switch off Momentum and Active-tracers (=T,S):
48 #ifdef ALLOW_OFFLINE
49 IF ( useOffLine ) THEN
50 CALL OFFLINE_RESET_PARMS( myThid )
51 ENDIF
52 #endif /* ALLOW_OFFLINE */
53
54 _BEGIN_MASTER(myThid)
55
56 C-- On/Off flags for each terms of the momentum equation
57 nonHydrostatic = momStepping .AND. nonHydrostatic
58 quasiHydrostatic = momStepping .AND. quasiHydrostatic
59 momAdvection = momStepping .AND. momAdvection
60 momViscosity = momStepping .AND. momViscosity
61 momForcing = momStepping .AND. momForcing
62 momTidalForcing = momForcing .AND. momTidalForcing
63 useCoriolis = momStepping .AND. useCoriolis
64 use3dCoriolis = useCoriolis .AND. use3dCoriolis
65 useCDscheme = momStepping .AND. useCDscheme
66 momPressureForcing= momStepping .AND. momPressureForcing
67 implicitIntGravWave=momPressureForcing .AND. implicitIntGravWave
68 momImplVertAdv = momAdvection .AND. momImplVertAdv
69 implicitViscosity= momViscosity .AND. implicitViscosity
70 useSmag3D = momViscosity .AND. useSmag3D
71 use3Dsolver = nonHydrostatic.OR. implicitIntGravWave
72 calc_wVelocity = momStepping .OR. exactConserv
73
74 #ifndef ALLOW_3D_VISCAH
75 IF ( viscAhDfile.NE.' ' .OR. viscAhZfile.NE.' ' ) THEN
76 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
77 & 'viscAhDfile and viscAhZfile cannot be used with'
78 CALL PRINT_ERROR( msgBuf, myThid )
79 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
80 & '"#undef ALLOW_3D_VISCAH" in MOM_COMMON_OPTIONS.h'
81 CALL PRINT_ERROR( msgBuf, myThid )
82 STOP 'ABNORMAL END: S/R SET_PARAMS'
83 c errCount = errCount + 1
84 ENDIF
85 #endif
86 #ifndef ALLOW_3D_VISCA4
87 IF ( viscA4Dfile.NE.' ' .OR. viscA4Zfile.NE.' ' ) THEN
88 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
89 & 'viscA4Dfile and viscA4Zfile cannot be used with'
90 CALL PRINT_ERROR( msgBuf, myThid )
91 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
92 & '"#undef ALLOW_3D_VISCA4" in MOM_COMMON_OPTIONS.h'
93 CALL PRINT_ERROR( msgBuf, myThid )
94 STOP 'ABNORMAL END: S/R SET_PARAMS'
95 ENDIF
96 #endif
97
98 #ifdef ALLOW_MOM_COMMON
99 C- On/Off flags for viscosity coefficients
100 useVariableVisc =
101 & viscAhGrid .NE.zeroRL .OR. viscA4Grid .NE.zeroRL
102 & .OR. viscC2smag .NE.zeroRL .OR. viscC4smag .NE.zeroRL
103 & .OR. viscC2leith.NE.zeroRL .OR. viscC2leithD.NE.zeroRL
104 & .OR. viscC4leith.NE.zeroRL .OR. viscC4leithD.NE.zeroRL
105 & .OR. viscAhDfile.NE.' ' .OR. viscAhZfile.NE.' '
106 & .OR. viscA4Dfile.NE.' ' .OR. viscA4Zfile.NE.' '
107
108 useHarmonicVisc = viscAh .NE.zeroRL
109 & .OR. viscAhD .NE.zeroRL .OR. viscAhZ .NE.zeroRL
110 & .OR. viscAhGrid .NE.zeroRL .OR. viscC2smag .NE.zeroRL
111 & .OR. viscC2leith.NE.zeroRL .OR. viscC2leithD.NE.zeroRL
112 & .OR. viscAhDfile.NE. ' ' .OR. viscAhZfile .NE. ' '
113
114 useBiharmonicVisc = viscA4.NE.zeroRL
115 & .OR. viscA4D .NE.zeroRL .OR. viscA4Z .NE.zeroRL
116 & .OR. viscA4Grid .NE.zeroRL .OR. viscC4smag .NE.zeroRL
117 & .OR. viscC4leith.NE.zeroRL .OR. viscC4leithD.NE.zeroRL
118 & .OR. viscA4Dfile.NE. ' ' .OR. viscA4Zfile .NE. ' '
119
120 useVariableVisc = momViscosity .AND. useVariableVisc
121 useHarmonicVisc = momViscosity .AND. useHarmonicVisc
122 useBiharmonicVisc = momViscosity .AND. useBiharmonicVisc
123 #endif /* ALLOW_MOM_COMMON */
124 IF ( bottomDragQuadratic.EQ.0. .OR. .NOT.momViscosity )
125 & selectBotDragQuadr = -1
126
127 C-- Free-surface & pressure method
128 uniformFreeSurfLev = usingZCoords
129 C- Note: comment line below to revert to full-cell hydrostatic-pressure
130 C calculation in surface grid-cell below ice-shelf
131 uniformFreeSurfLev = usingZCoords .AND. .NOT.useShelfIce
132 IF ( selectNHfreeSurf.NE.0 .AND.
133 & ( .NOT.nonHydrostatic .OR. usingPCoords
134 & .OR. .NOT.exactConserv
135 & ) ) THEN
136 WRITE(msgBuf,'(2A)') '** WARNING ** SET_PARMS: ',
137 & 'reset selectNHfreeSurf to zero'
138 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
139 & SQUEEZE_RIGHT, myThid )
140 selectNHfreeSurf = 0
141 ENDIF
142 #ifdef ALLOW_AUTODIFF
143 doResetHFactors = .TRUE.
144 #endif
145 #ifndef NONLIN_FRSURF
146 doResetHFactors = .FALSE.
147 #endif
148
149 C-- Set default Vorticity-Term Scheme:
150 IF ( vectorInvariantMomentum ) THEN
151 IF ( selectVortScheme.EQ.UNSET_I ) THEN
152 selectVortScheme = 1
153 IF ( upwindVorticity ) selectVortScheme = 0
154 IF ( highOrderVorticity ) selectVortScheme = 0
155 ENDIF
156 ELSEIF ( selectVortScheme.NE.UNSET_I ) THEN
157 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
158 & 'Vector-Invariant Momentum unused => ignore selectVortScheme'
159 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
160 & SQUEEZE_RIGHT, myThid )
161 ENDIF
162 C-- Momentum viscosity on/off flag.
163 IF ( momViscosity ) THEN
164 vfFacMom = 1. _d 0
165 ELSE
166 vfFacMom = 0. _d 0
167 ENDIF
168 C-- Momentum advection on/off flag.
169 IF ( momAdvection ) THEN
170 afFacMom = 1. _d 0
171 ELSE
172 afFacMom = 0. _d 0
173 ENDIF
174 C-- Momentum forcing on/off flag.
175 IF ( momForcing ) THEN
176 foFacMom = 1. _d 0
177 ELSE
178 foFacMom = 0. _d 0
179 ENDIF
180 C-- Coriolis term on/off flag.
181 IF ( useCoriolis ) THEN
182 cfFacMom = 1. _d 0
183 ELSE
184 cfFacMom = 0. _d 0
185 ENDIF
186 C-- Pressure term on/off flag.
187 IF ( momPressureForcing ) THEN
188 pfFacMom = 1. _d 0
189 ELSE
190 pfFacMom = 0. _d 0
191 ENDIF
192 C-- Metric terms on/off flag.
193 IF ( metricTerms ) THEN
194 mTFacMom = 1. _d 0
195 ELSE
196 mTFacMom = 0. _d 0
197 ENDIF
198
199 C-- Advection and Forcing for Temp and salt on/off flags
200 tempVertDiff4 = .FALSE.
201 saltVertDiff4 = .FALSE.
202 DO k=1,Nr
203 tempVertDiff4 = tempVertDiff4 .OR. ( diffKr4T(k).GT.0. _d 0 )
204 saltVertDiff4 = saltVertDiff4 .OR. ( diffKr4S(k).GT.0. _d 0 )
205 ENDDO
206 tempAdvection = tempStepping .AND. tempAdvection
207 tempVertDiff4 = tempStepping .AND. tempVertDiff4
208 tempForcing = tempStepping .AND. tempForcing
209 saltAdvection = saltStepping .AND. saltAdvection
210 saltVertDiff4 = saltStepping .AND. saltVertDiff4
211 saltForcing = saltStepping .AND. saltForcing
212 tempImplVertAdv = tempAdvection .AND. tempImplVertAdv
213 saltImplVertAdv = saltAdvection .AND. saltImplVertAdv
214 doThetaClimRelax = ( tempForcing .OR.( useOffLine.AND.useKPP ) )
215 & .AND. ( tauThetaClimRelax.GT.0. _d 0 )
216 doSaltClimRelax = ( saltForcing .OR.( useOffLine.AND.useKPP ) )
217 & .AND. ( tauSaltClimRelax .GT.0. _d 0 )
218
219 C-- Dynamically Active Tracers : set flags
220 tempIsActiveTr = momPressureForcing .AND. tempAdvection
221 saltIsActiveTr = momPressureForcing .AND. saltAdvection
222 IF ( eosType.EQ.'IDEALG' .AND. atm_Rq.EQ.0. ) THEN
223 saltIsActiveTr = .FALSE.
224 ELSEIF ( eosType.EQ.'LINEAR' ) THEN
225 IF ( tAlpha.EQ.0. ) tempIsActiveTr = .FALSE.
226 IF ( sBeta .EQ.0. ) saltIsActiveTr = .FALSE.
227 ENDIF
228
229 IF ( usingZCoords ) THEN
230 C-- Select which pressure to use in EOS:
231 C set default according to EOS type (as it was until chkpt65t)
232 IF ( selectP_inEOS_Zc.EQ.UNSET_I ) THEN
233 IF ( eosType .EQ. 'JMD95P' .OR. eosType .EQ. 'UNESCO'
234 & .OR. eosType .EQ. 'MDJWF' .OR. eosType .EQ. 'TEOS10'
235 & ) THEN
236 selectP_inEOS_Zc = 2
237 ELSE
238 selectP_inEOS_Zc = 0
239 ENDIF
240 ELSEIF ( selectP_inEOS_Zc.LT.0
241 & .OR. selectP_inEOS_Zc.GT.3 ) THEN
242 WRITE(msgBuf,'(A,I9,A)') 'SET_PARAMS: selectP_inEOS_Zc=',
243 & selectP_inEOS_Zc, ' : invalid selection'
244 CALL PRINT_ERROR( msgBuf, myThid )
245 STOP 'ABNORMAL END: S/R SET_PARAMS'
246 ELSEIF ( .NOT.nonHydrostatic ) THEN
247 selectP_inEOS_Zc = MIN( selectP_inEOS_Zc, 2 )
248 ENDIF
249 IF ( ( eosType .EQ. 'LINEAR' .OR. eosType .EQ. 'POLY3 ' )
250 & .AND. selectP_inEOS_Zc.NE.0 ) THEN
251 WRITE(msgBuf,'(A,I9,A)') 'SET_PARAMS: selectP_inEOS_Zc=',
252 & selectP_inEOS_Zc, ' : invalid with eosType=', eosType
253 CALL PRINT_ERROR( msgBuf, myThid )
254 STOP 'ABNORMAL END: S/R SET_PARAMS'
255 ENDIF
256 ELSE
257 selectP_inEOS_Zc = -1
258 ENDIF
259 C-- When using the dynamical pressure in EOS (with Z-coord.),
260 C needs to activate specific part of the code (restart & exchange)
261 storePhiHyd4Phys = selectP_inEOS_Zc.GE.2
262 C- pkg/atm_phys uses main-model geopotential:
263 storePhiHyd4Phys = storePhiHyd4Phys .OR. useAtm_Phys
264
265 C-- Adjust parameters related to length of the simulation
266
267 C- Need to adjust endTime for sub-timestep mismatch , since in
268 C several places, test for last iteration with time==endTime :
269 tmpVar = startTime + deltaTClock*DFLOAT(nTimeSteps)
270 IF ( endTime.NE.tmpVar ) THEN
271 IF ( ABS(endTime-tmpVar).GT.deltaTClock*1. _d -6 ) THEN
272 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
273 & '(endTime-baseTime) not multiple of time-step'
274 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
275 & SQUEEZE_RIGHT, myThid )
276 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
277 & 'Previous endTime=', endTime
278 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
279 & SQUEEZE_RIGHT, myThid )
280 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
281 & 'Adjusted endTime=', tmpVar
282 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
283 & SQUEEZE_RIGHT, myThid )
284 ENDIF
285 endTime = tmpVar
286 ENDIF
287
288 #ifdef ALLOW_LONGSTEP
289 IF ( usePTRACERS ) THEN
290 CALL LONGSTEP_CHECK_ITERS(myThid)
291 ENDIF
292 #endif /* ALLOW_LONGSTEP */
293
294 C-- After this point, main model parameters are not supposed to be modified.
295 WRITE(msgBuf,'(A,A)') 'SET_PARMS: done'
296 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
297 & SQUEEZE_RIGHT , 1)
298
299 _END_MASTER(myThid)
300
301 C-- Everyone else must wait for the parameters to be set
302 _BARRIER
303
304 RETURN
305 END

  ViewVC Help
Powered by ViewVC 1.1.22