/[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.21 - (show annotations) (download)
Sat Jan 10 20:24:58 2015 UTC (9 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65j, checkpoint65k, checkpoint65i, checkpoint65l, checkpoint65m
Changes since 1.20: +3 -1 lines
set useDynP_inEos_Zc=T when using pkg/atm_phys (uses geopotential totPhiHyd)
 (moved from atm_phys_init_fixed.F)

1 C $Header: /u/gcmpack/MITgcm/model/src/set_parms.F,v 1.20 2015/01/03 23:56:41 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 useCoriolis = momStepping .AND. useCoriolis
63 use3dCoriolis= useCoriolis .AND. use3dCoriolis
64 useCDscheme = momStepping .AND. useCDscheme
65 momPressureForcing= momStepping .AND. momPressureForcing
66 implicitIntGravWave=momPressureForcing .AND. implicitIntGravWave
67 momImplVertAdv = momAdvection .AND. momImplVertAdv
68 implicitViscosity= momViscosity .AND. implicitViscosity
69 useSmag3D = momViscosity .AND. useSmag3D
70 use3Dsolver = nonHydrostatic.OR. implicitIntGravWave
71 calc_wVelocity = momStepping .OR. exactConserv
72
73 #ifndef ALLOW_3D_VISCAH
74 IF ( viscAhDfile.NE.' ' .OR. viscAhZfile.NE.' ' ) THEN
75 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
76 & 'viscAhDfile and viscAhZfile cannot be used with'
77 CALL PRINT_ERROR( msgBuf, myThid )
78 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
79 & '"#undef ALLOW_3D_VISCAH" in MOM_COMMON_OPTIONS.h'
80 CALL PRINT_ERROR( msgBuf, myThid )
81 STOP 'ABNORMAL END: S/R SET_PARAMS'
82 c errCount = errCount + 1
83 ENDIF
84 #endif
85 #ifndef ALLOW_3D_VISCA4
86 IF ( viscA4Dfile.NE.' ' .OR. viscA4Zfile.NE.' ' ) THEN
87 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
88 & 'viscA4Dfile and viscA4Zfile cannot be used with'
89 CALL PRINT_ERROR( msgBuf, myThid )
90 WRITE(msgBuf,'(2A)') 'SET_PARAMS: ',
91 & '"#undef ALLOW_3D_VISCA4" in MOM_COMMON_OPTIONS.h'
92 CALL PRINT_ERROR( msgBuf, myThid )
93 STOP 'ABNORMAL END: S/R SET_PARAMS'
94 ENDIF
95 #endif
96
97 #ifdef ALLOW_MOM_COMMON
98 C- On/Off flags for viscosity coefficients
99 useVariableVisc =
100 & viscAhGrid .NE.zeroRL .OR. viscA4Grid .NE.zeroRL
101 & .OR. viscC2smag .NE.zeroRL .OR. viscC4smag .NE.zeroRL
102 & .OR. viscC2leith.NE.zeroRL .OR. viscC2leithD.NE.zeroRL
103 & .OR. viscC4leith.NE.zeroRL .OR. viscC4leithD.NE.zeroRL
104 & .OR. viscAhDfile.NE.' ' .OR. viscAhZfile.NE.' '
105 & .OR. viscA4Dfile.NE.' ' .OR. viscA4Zfile.NE.' '
106
107 useHarmonicVisc = viscAh .NE.zeroRL
108 & .OR. viscAhD .NE.zeroRL .OR. viscAhZ .NE.zeroRL
109 & .OR. viscAhGrid .NE.zeroRL .OR. viscC2smag .NE.zeroRL
110 & .OR. viscC2leith.NE.zeroRL .OR. viscC2leithD.NE.zeroRL
111 & .OR. viscAhDfile.NE. ' ' .OR. viscAhZfile .NE. ' '
112
113 useBiharmonicVisc = viscA4.NE.zeroRL
114 & .OR. viscA4D .NE.zeroRL .OR. viscA4Z .NE.zeroRL
115 & .OR. viscA4Grid .NE.zeroRL .OR. viscC4smag .NE.zeroRL
116 & .OR. viscC4leith.NE.zeroRL .OR. viscC4leithD.NE.zeroRL
117 & .OR. viscA4Dfile.NE. ' ' .OR. viscA4Zfile .NE. ' '
118
119 useVariableVisc = momViscosity .AND. useVariableVisc
120 useHarmonicVisc = momViscosity .AND. useHarmonicVisc
121 useBiharmonicVisc = momViscosity .AND. useBiharmonicVisc
122 #endif /* ALLOW_MOM_COMMON */
123 IF ( bottomDragQuadratic.EQ.0. .OR. .NOT.momViscosity )
124 & selectBotDragQuadr = -1
125
126 C-- Free-surface & pressure method
127 uniformFreeSurfLev = usingZCoords
128 C- Note: comment line below to revert to full-cell hydrostatic-pressure
129 C calculation in surface grid-cell below ice-shelf
130 uniformFreeSurfLev = usingZCoords .AND. .NOT.useShelfIce
131 IF ( selectNHfreeSurf.NE.0 .AND.
132 & ( .NOT.nonHydrostatic .OR. usingPCoords
133 & .OR. .NOT.exactConserv
134 & ) ) THEN
135 WRITE(msgBuf,'(2A)') '** WARNING ** SET_PARMS: ',
136 & 'reset selectNHfreeSurf to zero'
137 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
138 & SQUEEZE_RIGHT, myThid )
139 selectNHfreeSurf = 0
140 ENDIF
141 #ifdef ALLOW_AUTODIFF
142 doResetHFactors = .TRUE.
143 #endif
144 #ifndef NONLIN_FRSURF
145 doResetHFactors = .FALSE.
146 #endif
147
148 C-- Set default Vorticity-Term Scheme:
149 IF ( vectorInvariantMomentum ) THEN
150 IF ( selectVortScheme.EQ.UNSET_I ) THEN
151 selectVortScheme = 1
152 IF ( upwindVorticity ) selectVortScheme = 0
153 IF ( highOrderVorticity ) selectVortScheme = 0
154 ENDIF
155 ELSEIF ( selectVortScheme.NE.UNSET_I ) THEN
156 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
157 & 'Vector-Invariant Momentum unused => ignore selectVortScheme'
158 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
159 & SQUEEZE_RIGHT, myThid )
160 ENDIF
161 C-- Momentum viscosity on/off flag.
162 IF ( momViscosity ) THEN
163 vfFacMom = 1. _d 0
164 ELSE
165 vfFacMom = 0. _d 0
166 ENDIF
167 C-- Momentum advection on/off flag.
168 IF ( momAdvection ) THEN
169 afFacMom = 1. _d 0
170 ELSE
171 afFacMom = 0. _d 0
172 ENDIF
173 C-- Momentum forcing on/off flag.
174 IF ( momForcing ) THEN
175 foFacMom = 1. _d 0
176 ELSE
177 foFacMom = 0. _d 0
178 ENDIF
179 C-- Coriolis term on/off flag.
180 IF ( useCoriolis ) THEN
181 cfFacMom = 1. _d 0
182 ELSE
183 cfFacMom = 0. _d 0
184 ENDIF
185 C-- Pressure term on/off flag.
186 IF ( momPressureForcing ) THEN
187 pfFacMom = 1. _d 0
188 ELSE
189 pfFacMom = 0. _d 0
190 ENDIF
191 C-- Metric terms on/off flag.
192 IF ( metricTerms ) THEN
193 mTFacMom = 1. _d 0
194 ELSE
195 mTFacMom = 0. _d 0
196 ENDIF
197
198 C-- Advection and Forcing for Temp and salt on/off flags
199 tempVertDiff4 = .FALSE.
200 saltVertDiff4 = .FALSE.
201 DO k=1,Nr
202 tempVertDiff4 = tempVertDiff4 .OR. ( diffKr4T(k).GT.0. _d 0 )
203 saltVertDiff4 = saltVertDiff4 .OR. ( diffKr4S(k).GT.0. _d 0 )
204 ENDDO
205 tempAdvection = tempStepping .AND. tempAdvection
206 tempVertDiff4 = tempStepping .AND. tempVertDiff4
207 tempForcing = tempStepping .AND. tempForcing
208 saltAdvection = saltStepping .AND. saltAdvection
209 saltVertDiff4 = saltStepping .AND. saltVertDiff4
210 saltForcing = saltStepping .AND. saltForcing
211 tempImplVertAdv = tempAdvection .AND. tempImplVertAdv
212 saltImplVertAdv = saltAdvection .AND. saltImplVertAdv
213 doThetaClimRelax = tempForcing .AND.
214 & ( tauThetaClimRelax.GT.0. _d 0 )
215 doSaltClimRelax = saltForcing .AND.
216 & ( tauSaltClimRelax .GT.0. _d 0 )
217
218 C-- Dynamically Active Tracers : set flags
219 tempIsActiveTr = momPressureForcing .AND. tempAdvection
220 saltIsActiveTr = momPressureForcing .AND. saltAdvection
221 IF ( eosType.EQ.'IDEALG' .AND. atm_Rq.EQ.0. ) THEN
222 saltIsActiveTr = .FALSE.
223 ELSEIF ( eosType.EQ.'LINEAR' ) THEN
224 IF ( tAlpha.EQ.0. ) tempIsActiveTr = .FALSE.
225 IF ( sBeta .EQ.0. ) saltIsActiveTr = .FALSE.
226 ENDIF
227
228 C-- When using the dynamical pressure in EOS (with Z-coord.),
229 C needs to activate specific part of the code (restart & exchange)
230 c useDynP_inEos_Zc = .FALSE.
231 useDynP_inEos_Zc = ( fluidIsWater .AND. usingZCoords
232 & .AND. ( eosType .EQ. 'JMD95P' .OR.
233 & eosType .EQ. 'UNESCO' .OR.
234 & eosType .EQ. 'MDJWF' .OR.
235 & eosType .EQ. 'TEOS10' ) )
236 C- pkg/atm_phys uses main-model geopotential:
237 useDynP_inEos_Zc = useDynP_inEos_Zc .OR. useAtm_Phys
238
239 C-- Adjust parameters related to length of the simulation
240
241 C- Need to adjust endTime for sub-timestep mismatch , since in
242 C several places, test for last iteration with time==endTime :
243 tmpVar = startTime + deltaTClock*FLOAT(nTimeSteps)
244 IF ( endTime.NE.tmpVar ) THEN
245 IF ( ABS(endTime-tmpVar).GT.deltaTClock*1. _d -6 ) THEN
246 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
247 & '(endTime-baseTime) not multiple of time-step'
248 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
249 & SQUEEZE_RIGHT, myThid )
250 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
251 & 'Previous endTime=', endTime
252 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
253 & SQUEEZE_RIGHT, myThid )
254 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
255 & 'Adjusted endTime=', tmpVar
256 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
257 & SQUEEZE_RIGHT, myThid )
258 ENDIF
259 endTime = tmpVar
260 ENDIF
261
262 #ifdef ALLOW_LONGSTEP
263 IF ( usePTRACERS ) THEN
264 CALL LONGSTEP_CHECK_ITERS(myThid)
265 ENDIF
266 #endif /* ALLOW_LONGSTEP */
267
268 C-- After this point, main model parameters are not supposed to be modified.
269 WRITE(msgBuf,'(A,A)') 'SET_PARMS: done'
270 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
271 & SQUEEZE_RIGHT , 1)
272
273 _END_MASTER(myThid)
274
275 C-- Everyone else must wait for the parameters to be set
276 _BARRIER
277
278 RETURN
279 END

  ViewVC Help
Powered by ViewVC 1.1.22