/[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.8 - (show annotations) (download)
Tue Jul 19 13:02:45 2011 UTC (12 years, 9 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint63a
Changes since 1.7: +3 -2 lines
add TEOS10 to the scheme to set useDynP_inEos_Zc

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

  ViewVC Help
Powered by ViewVC 1.1.22