/[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.12 - (show annotations) (download)
Tue Dec 27 22:10:46 2011 UTC (12 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k
Changes since 1.11: +7 -10 lines
call S/R OFFLINE_RESET_PARMS to reset flags for off-line calculation

1 C $Header: /u/gcmpack/MITgcm/model/src/set_parms.F,v 1.11 2011/12/07 23:31:15 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 CBOP
9 C !ROUTINE: SET_PARMS
10 C !INTERFACE:
11 SUBROUTINE SET_PARMS( myThid )
12
13 C !DESCRIPTION:
14 C Set model "parameters" that might depend on the use of some pkgs;
15 C called from INITIALISE_FIXED, after INI_PARMS & PACKAGES_READPARAMS
16 C NOTES: After leaving this S/R, parameters will not change anymore.
17
18 C !USES:
19 IMPLICIT NONE
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "EOS.h"
24
25 C !INPUT/OUTPUT PARAMETERS:
26 C myThid :: My Thread Id number
27 INTEGER myThid
28
29 C !FUNCTIONS:
30 c INTEGER ILNBLNK
31 c EXTERNAL ILNBLNK
32
33 C !LOCAL VARIABLES:
34 CHARACTER*(MAX_LEN_MBUF) msgBuf
35 _RL tmpVar
36 CEOP
37
38 C-- Set (or reset) On/Off flags :
39
40 C- For off-line calculation, switch off Momentum and Active-tracers (=T,S):
41 #ifdef ALLOW_OFFLINE
42 IF ( useOffLine ) THEN
43 CALL OFFLINE_RESET_PARMS( myThid )
44 ENDIF
45 #endif /* ALLOW_OFFLINE */
46
47 _BEGIN_MASTER(myThid)
48
49 C-- On/Off flags for each terms of the momentum equation
50 nonHydrostatic = momStepping .AND. nonHydrostatic
51 quasiHydrostatic = momStepping .AND. quasiHydrostatic
52 momAdvection = momStepping .AND. momAdvection
53 momViscosity = momStepping .AND. momViscosity
54 momForcing = momStepping .AND. momForcing
55 useCoriolis = momStepping .AND. useCoriolis
56 use3dCoriolis= useCoriolis .AND. use3dCoriolis
57 useCDscheme = momStepping .AND. useCDscheme
58 momPressureForcing= momStepping .AND. momPressureForcing
59 implicitIntGravWave=momPressureForcing .AND. implicitIntGravWave
60 momImplVertAdv = momAdvection .AND. momImplVertAdv
61 implicitViscosity= momViscosity .AND. implicitViscosity
62 use3Dsolver = nonHydrostatic.OR. implicitIntGravWave
63 calc_wVelocity = momStepping .OR. exactConserv
64
65 C-- Free-surface & pressure method
66 IF ( selectNHfreeSurf.NE.0 .AND.
67 & ( .NOT.nonHydrostatic .OR. usingPCoords
68 & .OR. .NOT.exactConserv
69 & ) ) THEN
70 WRITE(msgBuf,'(2A)') '** WARNING ** SET_PARMS: ',
71 & 'reset selectNHfreeSurf to zero'
72 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
73 & SQUEEZE_RIGHT, myThid )
74 selectNHfreeSurf = 0
75 ENDIF
76 #ifdef ALLOW_AUTODIFF_TAMC
77 doResetHFactors = .TRUE.
78 #endif
79 #ifndef NONLIN_FRSURF
80 doResetHFactors = .FALSE.
81 #endif
82 C-- Set default Vorticity-Term Scheme:
83 IF ( vectorInvariantMomentum ) THEN
84 IF ( selectVortScheme.EQ.UNSET_I ) THEN
85 selectVortScheme = 1
86 IF ( upwindVorticity ) selectVortScheme = 0
87 IF ( highOrderVorticity ) selectVortScheme = 0
88 ENDIF
89 ELSEIF ( selectVortScheme.NE.UNSET_I ) THEN
90 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
91 & 'Vector-Invariant Momentum unused => ignore selectVortScheme'
92 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
93 & SQUEEZE_RIGHT, myThid )
94 ENDIF
95 C-- Momentum viscosity on/off flag.
96 IF ( momViscosity ) THEN
97 vfFacMom = 1. _d 0
98 ELSE
99 vfFacMom = 0. _d 0
100 ENDIF
101 C-- Momentum advection on/off flag.
102 IF ( momAdvection ) THEN
103 afFacMom = 1. _d 0
104 ELSE
105 afFacMom = 0. _d 0
106 ENDIF
107 C-- Momentum forcing on/off flag.
108 IF ( momForcing ) THEN
109 foFacMom = 1. _d 0
110 ELSE
111 foFacMom = 0. _d 0
112 ENDIF
113 C-- Coriolis term on/off flag.
114 IF ( useCoriolis ) THEN
115 cfFacMom = 1. _d 0
116 ELSE
117 cfFacMom = 0. _d 0
118 ENDIF
119 C-- Pressure term on/off flag.
120 IF ( momPressureForcing ) THEN
121 pfFacMom = 1. _d 0
122 ELSE
123 pfFacMom = 0. _d 0
124 ENDIF
125 C-- Metric terms on/off flag.
126 IF ( metricTerms ) THEN
127 mTFacMom = 1. _d 0
128 ELSE
129 mTFacMom = 0. _d 0
130 ENDIF
131
132 C-- Advection and Forcing for Temp and salt on/off flags
133 tempAdvection = tempStepping .AND. tempAdvection
134 tempForcing = tempStepping .AND. tempForcing
135 saltAdvection = saltStepping .AND. saltAdvection
136 saltForcing = saltStepping .AND. saltForcing
137 tempImplVertAdv = tempAdvection .AND. tempImplVertAdv
138 saltImplVertAdv = saltAdvection .AND. saltImplVertAdv
139 doThetaClimRelax = tempForcing .AND.
140 & ( tauThetaClimRelax.GT.0. _d 0 )
141 doSaltClimRelax = saltForcing .AND.
142 & ( tauSaltClimRelax .GT.0. _d 0 )
143
144 C-- Dynamically Active Tracers : set flags
145 tempIsActiveTr = momPressureForcing .AND. tempAdvection
146 saltIsActiveTr = momPressureForcing .AND. saltAdvection
147 IF ( eosType.EQ.'IDEALGAS' .AND. atm_Rq.EQ.0. ) THEN
148 saltIsActiveTr = .FALSE.
149 ELSEIF ( eosType.EQ.'LINEAR' ) THEN
150 IF ( tAlpha.EQ.0. ) tempIsActiveTr = .FALSE.
151 IF ( sBeta .EQ.0. ) saltIsActiveTr = .FALSE.
152 ENDIF
153
154 C-- When using the dynamical pressure in EOS (with Z-coord.),
155 C needs to activate specific part of the code (restart & exchange)
156 c useDynP_inEos_Zc = .FALSE.
157 useDynP_inEos_Zc = ( fluidIsWater .AND. usingZCoords
158 & .AND. ( eosType .EQ. 'JMD95P' .OR.
159 & eosType .EQ. 'UNESCO' .OR.
160 & eosType .EQ. 'MDJWF' .OR.
161 & eosType .EQ. 'TEOS10' ) )
162
163 C-- Adjust parameters related to length of the simulation
164
165 C- Need to adjust endTime for sub-timestep mismatch , since in
166 C several places, test for last iteration with time==endTime :
167 tmpVar = startTime + deltaTClock*FLOAT(nTimeSteps)
168 IF ( endTime.NE.tmpVar ) THEN
169 IF ( ABS(endTime-tmpVar).GT.deltaTClock*1. _d -6 ) THEN
170 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
171 & '(endTime-baseTime) not multiple of time-step'
172 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
173 & SQUEEZE_RIGHT, myThid )
174 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
175 & 'Previous endTime=', endTime
176 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
177 & SQUEEZE_RIGHT, myThid )
178 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
179 & 'Adjusted endTime=', tmpVar
180 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
181 & SQUEEZE_RIGHT, myThid )
182 ENDIF
183 endTime = tmpVar
184 ENDIF
185
186 #ifdef ALLOW_LONGSTEP
187 IF ( usePTRACERS ) THEN
188 CALL LONGSTEP_CHECK_ITERS(myThid)
189 ENDIF
190 #endif /* ALLOW_LONGSTEP */
191
192 C-- After this point, main model parameters are not supposed to be modified.
193 WRITE(msgBuf,'(A,A)') 'SET_PARMS: done'
194 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
195 & SQUEEZE_RIGHT , 1)
196
197 _END_MASTER(myThid)
198
199 C-- Everyone else must wait for the parameters to be set
200 _BARRIER
201
202 RETURN
203 END

  ViewVC Help
Powered by ViewVC 1.1.22