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

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

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


Revision 1.5 - (hide annotations) (download)
Fri Jun 26 23:10:09 2009 UTC (15 years ago) by jahn
Branch: MAIN
CVS Tags: checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.4: +8 -2 lines
add package longstep

1 jahn 1.5 C $Header: /u/gcmpack/MITgcm/model/src/set_parms.F,v 1.4 2008/04/05 21:24:08 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4 jahn 1.5 #include "PACKAGES_CONFIG.h"
5 jmc 1.1 #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 jmc 1.4 #include "EOS.h"
24 jmc 1.1
25     C !INPUT/OUTPUT PARAMETERS:
26     C myThid - Number of this instance of SET_PARMS
27     INTEGER myThid
28    
29     C !LOCAL VARIABLES:
30     CHARACTER*(MAX_LEN_MBUF) msgBuf
31     c INTEGER IL, iUnit
32     c INTEGER ILNBLNK
33     c EXTERNAL ILNBLNK
34    
35     CEOP
36    
37     _BEGIN_MASTER(myThid)
38    
39     IF ( useOffLine ) THEN
40     WRITE(msgBuf,'(A,A)') 'S/R SET_PARMS: ',
41     & ' Off-Line => turn off Temp,Salt & Mom_Stepping flags'
42     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
43     & SQUEEZE_RIGHT , 1)
44     tempStepping = .FALSE.
45     saltStepping = .FALSE.
46     momStepping = .FALSE.
47     ENDIF
48    
49     C-- Set (or reset) On/Off flags :
50    
51     C-- On/Off flags for each terms of the momentum equation
52     nonHydrostatic = momStepping .AND. nonHydrostatic
53     quasiHydrostatic = momStepping .AND. quasiHydrostatic
54     momAdvection = momStepping .AND. momAdvection
55     momViscosity = momStepping .AND. momViscosity
56     momForcing = momStepping .AND. momForcing
57     useCoriolis = momStepping .AND. useCoriolis
58 jmc 1.2 use3dCoriolis= useCoriolis .AND. use3dCoriolis
59 jmc 1.1 useCDscheme = momStepping .AND. useCDscheme
60     momPressureForcing= momStepping .AND. momPressureForcing
61     implicitIntGravWave=momPressureForcing .AND. implicitIntGravWave
62     momImplVertAdv = momAdvection .AND. momImplVertAdv
63     implicitViscosity= momViscosity .AND. implicitViscosity
64     use3Dsolver = nonHydrostatic.OR. implicitIntGravWave
65 jmc 1.3 C-- Set default Vorticity-Term Scheme:
66     IF ( vectorInvariantMomentum ) THEN
67     IF ( selectVortScheme.EQ.UNSET_I ) THEN
68     selectVortScheme = 1
69     IF ( upwindVorticity ) selectVortScheme = 0
70     IF ( highOrderVorticity ) selectVortScheme = 0
71     ENDIF
72     ELSEIF ( selectVortScheme.NE.UNSET_I ) THEN
73     WRITE(msgBuf,'(A,A)') '** WARNING ** SET_PARMS: ',
74     & 'Vector-Invariant Momentum unused => ignore selectVortScheme'
75     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit, SQUEEZE_RIGHT, 1 )
76     ENDIF
77 jmc 1.1 C-- Momentum viscosity on/off flag.
78     IF ( momViscosity ) THEN
79     vfFacMom = 1.D0
80     ELSE
81     vfFacMom = 0.D0
82     ENDIF
83     C-- Momentum advection on/off flag.
84     IF ( momAdvection ) THEN
85     afFacMom = 1.D0
86     ELSE
87     afFacMom = 0.D0
88     ENDIF
89     C-- Momentum forcing on/off flag.
90     IF ( momForcing ) THEN
91     foFacMom = 1.D0
92     ELSE
93     foFacMom = 0.D0
94     ENDIF
95     C-- Coriolis term on/off flag.
96     IF ( useCoriolis ) THEN
97     cfFacMom = 1.D0
98     ELSE
99     cfFacMom = 0.D0
100     ENDIF
101     C-- Pressure term on/off flag.
102     IF ( momPressureForcing ) THEN
103     pfFacMom = 1.D0
104     ELSE
105     pfFacMom = 0.D0
106     ENDIF
107     C-- Metric terms on/off flag.
108     IF ( metricTerms ) THEN
109     mTFacMom = 1.D0
110     ELSE
111     mTFacMom = 0.D0
112     ENDIF
113    
114     C-- Advection and Forcing for Temp and salt on/off flags
115     tempAdvection = tempStepping .AND. tempAdvection
116     tempForcing = tempStepping .AND. tempForcing
117     saltAdvection = saltStepping .AND. saltAdvection
118     saltForcing = saltStepping .AND. saltForcing
119     tempImplVertAdv = tempAdvection .AND. tempImplVertAdv
120     saltImplVertAdv = saltAdvection .AND. saltImplVertAdv
121    
122 jmc 1.4 C-- Dynamically Active Tracers : set flags
123     tempIsActiveTr = momPressureForcing .AND. tempAdvection
124     saltIsActiveTr = momPressureForcing .AND. saltAdvection
125     IF ( eosType.EQ.'IDEALGAS' .AND. atm_Rq.EQ.0. ) THEN
126     saltIsActiveTr = .FALSE.
127     ELSEIF ( eosType.EQ.'LINEAR' ) THEN
128     IF ( tAlpha.EQ.0. ) tempIsActiveTr = .FALSE.
129     IF ( sBeta .EQ.0. ) saltIsActiveTr = .FALSE.
130     ENDIF
131    
132 jmc 1.1 C-- When using the dynamical pressure in EOS (with Z-coord.),
133     C needs to activate specific part of the code (restart & exchange)
134     c useDynP_inEos_Zc = .FALSE.
135     useDynP_inEos_Zc = ( fluidIsWater .AND. usingZCoords
136     & .AND. ( eosType .EQ. 'JMD95P' .OR.
137     & eosType .EQ. 'UNESCO' .OR.
138     & eosType .EQ. 'MDJWF' ) )
139    
140 jahn 1.5 #ifdef ALLOW_LONGSTEP
141     IF ( usePTRACERS ) THEN
142     CALL LONGSTEP_CHECK_ITERS(myThid)
143     ENDIF
144     #endif /* ALLOW_LONGSTEP */
145    
146 jmc 1.1 C-- After this point, main model parameters are not supposed to be modified.
147     WRITE(msgBuf,'(A,A)') 'SET_PARMS: done'
148     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
149     & SQUEEZE_RIGHT , 1)
150    
151     _END_MASTER(myThid)
152    
153     C-- Everyone else must wait for the parameters to be set
154     _BARRIER
155    
156     RETURN
157     END

  ViewVC Help
Powered by ViewVC 1.1.22