/[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.16 - (show annotations) (download)
Fri Jul 13 20:44:18 2012 UTC (11 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint64
Changes since 1.15: +3 -2 lines
fix saltIsActiveTr setting for IdealGas eosType (eosType is 6 character long)

1 C $Header: /u/gcmpack/MITgcm/model/src/set_parms.F,v 1.15 2012/06/15 13:20:04 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 INTEGER k
36 _RL tmpVar
37 CEOP
38
39 C-- Set (or reset) On/Off flags :
40
41 C- For off-line calculation, switch off Momentum and Active-tracers (=T,S):
42 #ifdef ALLOW_OFFLINE
43 IF ( useOffLine ) THEN
44 CALL OFFLINE_RESET_PARMS( myThid )
45 ENDIF
46 #endif /* ALLOW_OFFLINE */
47
48 _BEGIN_MASTER(myThid)
49
50 C-- On/Off flags for each terms of the momentum equation
51 nonHydrostatic = momStepping .AND. nonHydrostatic
52 quasiHydrostatic = momStepping .AND. quasiHydrostatic
53 momAdvection = momStepping .AND. momAdvection
54 momViscosity = momStepping .AND. momViscosity
55 momForcing = momStepping .AND. momForcing
56 useCoriolis = momStepping .AND. useCoriolis
57 use3dCoriolis= useCoriolis .AND. use3dCoriolis
58 useCDscheme = momStepping .AND. useCDscheme
59 momPressureForcing= momStepping .AND. momPressureForcing
60 implicitIntGravWave=momPressureForcing .AND. implicitIntGravWave
61 momImplVertAdv = momAdvection .AND. momImplVertAdv
62 implicitViscosity= momViscosity .AND. implicitViscosity
63 use3Dsolver = nonHydrostatic.OR. implicitIntGravWave
64 calc_wVelocity = momStepping .OR. exactConserv
65
66 C-- Free-surface & pressure method
67 uniformFreeSurfLev = usingZCoords
68 C- Note: comment line below to revert to full-cell hydrostatic-pressure
69 C calculation in surface grid-cell below ice-shelf
70 uniformFreeSurfLev = usingZCoords .AND. .NOT.useShelfIce
71 IF ( selectNHfreeSurf.NE.0 .AND.
72 & ( .NOT.nonHydrostatic .OR. usingPCoords
73 & .OR. .NOT.exactConserv
74 & ) ) THEN
75 WRITE(msgBuf,'(2A)') '** WARNING ** SET_PARMS: ',
76 & 'reset selectNHfreeSurf to zero'
77 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
78 & SQUEEZE_RIGHT, myThid )
79 selectNHfreeSurf = 0
80 ENDIF
81 #ifdef ALLOW_AUTODIFF_TAMC
82 doResetHFactors = .TRUE.
83 #endif
84 #ifndef NONLIN_FRSURF
85 doResetHFactors = .FALSE.
86 #endif
87
88 C-- Set default Vorticity-Term Scheme:
89 IF ( vectorInvariantMomentum ) THEN
90 IF ( selectVortScheme.EQ.UNSET_I ) THEN
91 selectVortScheme = 1
92 IF ( upwindVorticity ) selectVortScheme = 0
93 IF ( highOrderVorticity ) selectVortScheme = 0
94 ENDIF
95 ELSEIF ( selectVortScheme.NE.UNSET_I ) THEN
96 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
97 & 'Vector-Invariant Momentum unused => ignore selectVortScheme'
98 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
99 & SQUEEZE_RIGHT, myThid )
100 ENDIF
101 C-- Momentum viscosity on/off flag.
102 IF ( momViscosity ) THEN
103 vfFacMom = 1. _d 0
104 ELSE
105 vfFacMom = 0. _d 0
106 ENDIF
107 C-- Momentum advection on/off flag.
108 IF ( momAdvection ) THEN
109 afFacMom = 1. _d 0
110 ELSE
111 afFacMom = 0. _d 0
112 ENDIF
113 C-- Momentum forcing on/off flag.
114 IF ( momForcing ) THEN
115 foFacMom = 1. _d 0
116 ELSE
117 foFacMom = 0. _d 0
118 ENDIF
119 C-- Coriolis term on/off flag.
120 IF ( useCoriolis ) THEN
121 cfFacMom = 1. _d 0
122 ELSE
123 cfFacMom = 0. _d 0
124 ENDIF
125 C-- Pressure term on/off flag.
126 IF ( momPressureForcing ) THEN
127 pfFacMom = 1. _d 0
128 ELSE
129 pfFacMom = 0. _d 0
130 ENDIF
131 C-- Metric terms on/off flag.
132 IF ( metricTerms ) THEN
133 mTFacMom = 1. _d 0
134 ELSE
135 mTFacMom = 0. _d 0
136 ENDIF
137
138 C-- Advection and Forcing for Temp and salt on/off flags
139 tempVertDiff4 = .FALSE.
140 saltVertDiff4 = .FALSE.
141 DO k=1,Nr
142 tempVertDiff4 = tempVertDiff4 .OR. ( diffKr4T(k).GT.0. _d 0 )
143 saltVertDiff4 = saltVertDiff4 .OR. ( diffKr4S(k).GT.0. _d 0 )
144 ENDDO
145 tempAdvection = tempStepping .AND. tempAdvection
146 tempVertDiff4 = tempStepping .AND. tempVertDiff4
147 tempForcing = tempStepping .AND. tempForcing
148 saltAdvection = saltStepping .AND. saltAdvection
149 saltVertDiff4 = saltStepping .AND. saltVertDiff4
150 saltForcing = saltStepping .AND. saltForcing
151 tempImplVertAdv = tempAdvection .AND. tempImplVertAdv
152 saltImplVertAdv = saltAdvection .AND. saltImplVertAdv
153 doThetaClimRelax = tempForcing .AND.
154 & ( tauThetaClimRelax.GT.0. _d 0 )
155 doSaltClimRelax = saltForcing .AND.
156 & ( tauSaltClimRelax .GT.0. _d 0 )
157
158 C-- Dynamically Active Tracers : set flags
159 tempIsActiveTr = momPressureForcing .AND. tempAdvection
160 saltIsActiveTr = momPressureForcing .AND. saltAdvection
161 IF ( eosType.EQ.'IDEALG' .AND. atm_Rq.EQ.0. ) THEN
162 saltIsActiveTr = .FALSE.
163 ELSEIF ( eosType.EQ.'LINEAR' ) THEN
164 IF ( tAlpha.EQ.0. ) tempIsActiveTr = .FALSE.
165 IF ( sBeta .EQ.0. ) saltIsActiveTr = .FALSE.
166 ENDIF
167
168 C-- When using the dynamical pressure in EOS (with Z-coord.),
169 C needs to activate specific part of the code (restart & exchange)
170 c useDynP_inEos_Zc = .FALSE.
171 useDynP_inEos_Zc = ( fluidIsWater .AND. usingZCoords
172 & .AND. ( eosType .EQ. 'JMD95P' .OR.
173 & eosType .EQ. 'UNESCO' .OR.
174 & eosType .EQ. 'MDJWF' .OR.
175 & eosType .EQ. 'TEOS10' ) )
176
177 C-- Adjust parameters related to length of the simulation
178
179 C- Need to adjust endTime for sub-timestep mismatch , since in
180 C several places, test for last iteration with time==endTime :
181 tmpVar = startTime + deltaTClock*FLOAT(nTimeSteps)
182 IF ( endTime.NE.tmpVar ) THEN
183 IF ( ABS(endTime-tmpVar).GT.deltaTClock*1. _d -6 ) THEN
184 WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
185 & '(endTime-baseTime) not multiple of time-step'
186 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
187 & SQUEEZE_RIGHT, myThid )
188 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
189 & 'Previous endTime=', endTime
190 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
191 & SQUEEZE_RIGHT, myThid )
192 WRITE(msgBuf,'(2A,1PE20.13)') '** WARNING ** SET_PARMS: ',
193 & 'Adjusted endTime=', tmpVar
194 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
195 & SQUEEZE_RIGHT, myThid )
196 ENDIF
197 endTime = tmpVar
198 ENDIF
199
200 #ifdef ALLOW_LONGSTEP
201 IF ( usePTRACERS ) THEN
202 CALL LONGSTEP_CHECK_ITERS(myThid)
203 ENDIF
204 #endif /* ALLOW_LONGSTEP */
205
206 C-- After this point, main model parameters are not supposed to be modified.
207 WRITE(msgBuf,'(A,A)') 'SET_PARMS: done'
208 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
209 & SQUEEZE_RIGHT , 1)
210
211 _END_MASTER(myThid)
212
213 C-- Everyone else must wait for the parameters to be set
214 _BARRIER
215
216 RETURN
217 END

  ViewVC Help
Powered by ViewVC 1.1.22