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

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

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


Revision 1.13 - (hide annotations) (download)
Mon Jun 8 18:45:28 1998 UTC (25 years, 11 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint5
Changes since 1.12: +2 -2 lines
Various corrections:
 o implicitDiffusion was missing from PARAMS.h (obviously forgot to commit)
 o maskUp in calc_common_fact() is now correct
 o find_rho() now has the proper "referencing" for "LINEAR" eos-mode
   [also affected a call from dynamics()]

1 adcroft 1.13 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_parms.F,v 1.12 1998/06/01 22:27:14 adcroft Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.h"
4    
5     SUBROUTINE INI_PARMS( myThid )
6     C /==========================================================\
7     C | SUBROUTINE INI_PARMS |
8     C | o Routine to set model "parameters" |
9     C |==========================================================|
10     C | Notes: |
11     C | ====== |
12     C | The present version of this routine is a place-holder. |
13     C | A production version needs to handle parameters from an |
14     C | external file and possibly reading in some initial field |
15     C | values. |
16     C \==========================================================/
17    
18     C === Global variables ===
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "PARAMS.h"
22     #include "CG2D.h"
23    
24     C === Routine arguments ===
25     C myThid - Number of this instance of INI_PARMS
26     INTEGER myThid
27    
28     C === Local variables ===
29     C dxSpacing, dySpacing - Default spacing in X and Y.
30     C Units are that of coordinate system
31     C i.e. cartesian => metres
32     C s. polar => degrees
33     C goptCount - Used to count the nuber of grid options
34     C (only one is allowed! )
35     C msgBuf - Informational/error meesage buffer
36     C errIO - IO error flag
37     C iUnit - Work variable for IO unit number
38     C record - Work variable for IO buffer
39     C K, I, J - Loop counters
40     REAL dxSpacing
41     REAL dySpacing
42     CHARACTER*(MAX_LEN_MBUF) msgBuf
43     CHARACTER*(MAX_LEN_PREC) record
44     INTEGER goptCount
45     INTEGER K, I, J, IL, iUnit
46     INTEGER errIO
47     INTEGER IFNBLNK
48     EXTERNAL IFNBLNK
49     INTEGER ILNBLNK
50     EXTERNAL ILNBLNK
51    
52     C-- Continuous equation parameters
53     NAMELIST /PARM01/
54 cnh 1.8 & gravity, gBaro, rhonil, tAlpha, sBeta, f0, beta,
55 cnh 1.1 & viscAh, viscAz, viscA4,
56     & diffKhT, diffKzT, diffK4T,
57     & diffKhS, diffKzS, diffK4S,
58 adcroft 1.6 & GMmaxslope,GMlength,GMalpha,GMdepth,GMkbackground,
59 adcroft 1.11 & tRef, sRef, eosType,
60 cnh 1.1 & momViscosity, momAdvection, momForcing, useCoriolis,
61 cnh 1.9 & momPressureForcing,
62 cnh 1.1 & tempDiffusion, tempAdvection, tempForcing,
63 cnh 1.8 & saltDiffusion, saltAdvection, saltForcing,
64 cnh 1.10 & implicitFreeSurface, rigidLid, freeSurfFac,
65 adcroft 1.12 & tempStepping, momStepping, implicitDiffusion
66 cnh 1.1
67     C-- Elliptic solver parameters
68     NAMELIST /PARM02/
69 cnh 1.7 & cg2dMaxIters, cg2dChkResFreq, cg2dTargetResidual, cg2dpcOffDFac
70 cnh 1.1
71     C-- Time stepping parammeters
72     NAMELIST /PARM03/
73 cnh 1.5 & nIter0, nTimeSteps, deltaT, deltaTmom, deltaTtracer, abEps, tauCD, rCD,
74 cnh 1.9 & startTime, endTime, chkPtFreq, dumpFreq, deltaTClock, pChkPtFreq,
75     & cAdjFreq
76 cnh 1.1
77     C-- Gridding parameters
78     NAMELIST /PARM04/
79     & usingCartesianGrid, delZ, dxSpacing, dySpacing, delX, delY,
80     & usingSphericalPolarGrid, phiMin, thetaMin, rSphere,
81     & l, m, n
82    
83     C
84     _BEGIN_MASTER(myThid)
85    
86     C-- Open the parameter file
87     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
88     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
89     OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',err=1,IOSTAT=errIO)
90     IF ( errIO .GE. 0 ) GOTO 2
91     1 CONTINUE
92     WRITE(msgBuf,'(A)')
93     & 'S/R INI_PARMS'
94     CALL PRINT_ERROR( msgBuf , 1)
95     WRITE(msgBuf,'(A)')
96     & 'Unable to open model parameter'
97     CALL PRINT_ERROR( msgBuf , 1)
98     WRITE(msgBuf,'(A)')
99     & 'file "data"'
100     CALL PRINT_ERROR( msgBuf , 1)
101     CALL MODELDATA_EXAMPLE( myThid )
102     STOP 'ABNORMAL END: S/R INI_PARMS'
103     2 CONTINUE
104    
105     1000 CONTINUE
106     READ(modelDataUnit,FMT='(A)',END=1001) RECORD
107     IL = MAX(ILNBLNK(RECORD),1)
108     IF ( RECORD(1:1) .NE. commentCharacter )
109     & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
110     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
111     GOTO 1000
112     1001 CONTINUE
113     CLOSE(modelDataUnit)
114    
115     C-- Report contents of model parameter file
116     WRITE(msgBuf,'(A)')
117     &'// ======================================================='
118     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
119     WRITE(msgBuf,'(A)') '// Model parameter file "data"'
120     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
121     WRITE(msgBuf,'(A)')
122     &'// ======================================================='
123     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
124     & SQUEEZE_RIGHT , 1)
125     iUnit = scrUnit2
126     REWIND(iUnit)
127     2000 CONTINUE
128     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
129     IL = MAX(ILNBLNK(RECORD),1)
130     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
131     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
132     GOTO 2000
133     2001 CONTINUE
134     CLOSE(iUnit)
135     WRITE(msgBuf,'(A)') ' '
136     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
137     & SQUEEZE_RIGHT , 1)
138    
139    
140     C-- Read settings from model parameter file "data".
141     iUnit = scrUnit1
142     REWIND(iUnit)
143    
144     C-- Set default "physical" parameters
145     DO K =1,Nz
146     tRef(K) = 30.D0 - FLOAT(K)
147     ENDDO
148     gravity = 9.81 D0
149 cnh 1.8 gBaro = gravity
150 cnh 1.1 rhoNil = 999.8 D0
151     f0=1.D-4
152     beta = 1. _d -11
153     viscAh=1.d3
154     viscA4=0.
155     viscAz=1.d-3
156     diffKhT=1.0d3
157     diffKzT=1.d-5
158     diffKhS=1.0d3
159     diffKzS=1.d-1
160     diffK4T=0.
161     diffK4S=0.
162 adcroft 1.6 GMmaxslope=1.d-2
163     GMlength=200.d3
164     GMalpha=0.
165     GMdepth=1000.
166     GMkbackground=0.
167 adcroft 1.11 tAlpha=2.d-4
168     sBeta=1.d-5
169 adcroft 1.13 eosType='LINEAR'
170 cnh 1.8 implicitFreeSurface = .TRUE.
171     rigidLid = .FALSE.
172     freeSurfFac = 1. _d 0
173 cnh 1.9 momViscosity = .TRUE.
174     momAdvection = .TRUE.
175     momForcing = .TRUE.
176     useCoriolis = .TRUE.
177     momPressureForcing = .TRUE.
178 cnh 1.10 momStepping = .TRUE.
179     tempStepping = .TRUE.
180 adcroft 1.12 implicitDiffusion = .FALSE.
181 cnh 1.1 READ(UNIT=iUnit,NML=PARM01,IOSTAT=errIO,err=3)
182     IF ( errIO .GE. 0 ) GOTO 4
183     3 CONTINUE
184     WRITE(msgBuf,'(A)')
185     & 'S/R INI_PARMS'
186     CALL PRINT_ERROR( msgBuf , 1)
187     WRITE(msgBuf,'(A)')
188     & 'Error reading numerical model '
189     CALL PRINT_ERROR( msgBuf , 1)
190     WRITE(msgBuf,'(A)')
191     & 'parameter file "data"'
192     CALL PRINT_ERROR( msgBuf , 1)
193     WRITE(msgBuf,'(A)')
194     & 'Problem in namelist PARM01'
195     CALL PRINT_ERROR( msgBuf , 1)
196     CALL MODELDATA_EXAMPLE( myThid )
197     STOP 'ABNORMAL END: S/R INI_PARMS'
198     4 CONTINUE
199 cnh 1.8 IF ( implicitFreeSurface ) freeSurfFac = 1. _d 0
200     IF ( rigidLid ) freeSurfFac = 0. _d 0
201 cnh 1.9 IF ( momViscosity ) THEN
202     vfFacMom = 1. _d 0
203     ELSE
204     vfFacMom = 0. _d 0
205     ENDIF
206     IF ( momAdvection ) THEN
207     afFacMom = 1. _d 0
208     ELSE
209     afFacMom = 0. _d 0
210     ENDIF
211     IF ( momForcing ) THEN
212     foFacMom = 1. _d 0
213     ELSE
214     foFacMom = 0. _d 0
215     ENDIF
216     IF ( useCoriolis ) THEN
217     cfFacMom = 1. _d 0
218     ELSE
219     cfFacMom = 0. _d 0
220     ENDIF
221     IF ( momPressureForcing ) THEN
222     pfFacMom = 1. _d 0
223     ELSE
224     pfFacMom = 0. _d 0
225     ENDIF
226 cnh 1.8
227     IF ( implicitFreeSurface .AND. rigidLid ) THEN
228     WRITE(msgBuf,'(A)')
229     & 'S/R INI_PARMS: Cannot select implicitFreeSurface and rigidLid.'
230     CALL PRINT_ERROR( msgBuf , myThid)
231     STOP 'ABNORMAL END: S/R INI_PARMS'
232     ENDIF
233 cnh 1.1
234     C-- Elliptic solver parameters
235     cg2dMaxIters = 150
236     cg2dTargetResidual = 1. _d -7
237     cg2dChkResFreq = 1
238 cnh 1.7 cg2dpcOffDFac = 0.51 _d 0
239 cnh 1.1 READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)
240     IF ( errIO .GE. 0 ) GOTO 6
241     5 CONTINUE
242     WRITE(msgBuf,'(A)')
243     & 'S/R INI_PARMS'
244     CALL PRINT_ERROR( msgBuf , 1)
245     WRITE(msgBuf,'(A)')
246     & 'Error reading numerical model '
247     CALL PRINT_ERROR( msgBuf , 1)
248     WRITE(msgBuf,'(A)')
249     & 'parameter file "data".'
250     CALL PRINT_ERROR( msgBuf , 1)
251     WRITE(msgBuf,'(A)')
252     & 'Problem in namelist PARM02'
253     CALL PRINT_ERROR( msgBuf , 1)
254     CALL MODELDATA_EXAMPLE( myThid )
255     STOP 'ABNORMAL END: S/R INI_PARMS'
256     6 CONTINUE
257    
258     C-- Time stepping parameters
259     startTime = 0.
260 cnh 1.4 nTimeSteps = 0
261     endTime = 0.
262 cnh 1.1 nIter0 = 0
263 cnh 1.4 deltaT = 0.
264 cnh 1.7 deltaTClock = 0.
265 cnh 1.4 deltaTtracer = 0.
266     deltaTMom = 0.
267 cnh 1.1 abEps = 0.01
268 cnh 1.7 pchkPtFreq = 0.
269 cnh 1.1 chkPtFreq = 3600.*25
270     dumpFreq = 3600.*100
271 cnh 1.7 writeStatePrec = precFloat32
272     nCheckLev = 1
273     checkPtSuff(1) = 'ckptA'
274     checkPtSuff(2) = 'ckptB'
275 cnh 1.9 cAdjFreq = -1. _d 0
276 cnh 1.1 READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)
277     IF ( errIO .GE. 0 ) GOTO 8
278     7 CONTINUE
279     WRITE(msgBuf,'(A)')
280     & 'S/R INI_PARMS'
281     CALL PRINT_ERROR( msgBuf , 1)
282     WRITE(msgBuf,'(A)')
283     & 'Error reading numerical model '
284     CALL PRINT_ERROR( msgBuf , 1)
285     WRITE(msgBuf,'(A)')
286     & 'parameter file "data"'
287     CALL PRINT_ERROR( msgBuf , 1)
288     WRITE(msgBuf,'(A)')
289     & 'Problem in namelist PARM03'
290     CALL PRINT_ERROR( msgBuf , 1)
291     CALL MODELDATA_EXAMPLE( myThid )
292     STOP 'ABNORMAL END: S/R INI_PARMS'
293     8 CONTINUE
294 cnh 1.4 C Process "timestepping" params
295     C o Time step size
296     IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
297     IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
298     IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
299     IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
300 cnh 1.7 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
301 cnh 1.9 C o Convection frequency
302     IF ( cAdjFreq .LT. 0. ) THEN
303     cAdjFreq = deltaTClock
304     ENDIF
305 cnh 1.4 C o Time step count
306     IF ( endTime .NE. 0 ) THEN
307 cnh 1.7 IF ( deltaTClock .NE. 0 ) nTimeSteps =
308     & INT((endTime-startTime)/deltaTClock)
309 cnh 1.4 ENDIF
310     C o Finish time
311 cnh 1.7 IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock
312 cnh 1.1
313     C-- Grid parameters
314     C In cartesian coords distances are in metres
315     usingCartesianGrid = .TRUE.
316     DO K =1,Nz
317     delZ(K) = 100. _d 0
318     ENDDO
319     dxSpacing = 20. _d 0 * 1000. _d 0
320     dySpacing = 20. _d 0 * 1000. _d 0
321     DO i=1,Nx
322     delX(i) = dxSpacing
323     ENDDO
324     DO j=1,Ny
325     delY(j) = dySpacing
326     ENDDO
327     C In spherical polar distances are in degrees
328     usingSphericalPolarGrid = .FALSE.
329     IF ( usingSphericalPolarGrid ) THEN
330     phiMin = -5.0
331     thetaMin = 0.
332     dxSpacing = 1.
333     dySpacing = 1.
334     rSphere = 6370. * 1. _d 3
335     DO I=1,Nx
336     delX(I) = dxSpacing
337     ENDDO
338     DO J=1,Ny
339     delY(J) = dySpacing
340     ENDDO
341     ENDIF
342    
343     READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO,err=9)
344     IF ( errIO .GE. 0 ) GOTO 10
345     9 CONTINUE
346     WRITE(msgBuf,'(A)')
347     & 'S/R INI_PARMS'
348     CALL PRINT_ERROR( msgBuf , 1)
349     WRITE(msgBuf,'(A)')
350     & 'Error reading numerical model '
351     CALL PRINT_ERROR( msgBuf , 1)
352     WRITE(msgBuf,'(A)')
353     & 'parameter file "data"'
354     CALL PRINT_ERROR( msgBuf , 1)
355     WRITE(msgBuf,'(A)')
356     & 'Problem in namelist PARM04'
357     CALL PRINT_ERROR( msgBuf , 1)
358     CALL MODELDATA_EXAMPLE( myThid )
359     STOP 'ABNORMAL END: S/R INI_PARMS'
360     10 CONTINUE
361 adcroft 1.11
362     C Initialize EOS coefficients (3rd order polynomial)
363     IF (eostype.eq.'POLY3') THEN
364     OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
365     READ(37,*) I
366     IF (I.NE.Nz) THEN
367     WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'
368     WRITE(0,*) ' because bad # of levels in data'
369     STOP 'Bad data in POLY3.COEFFS'
370     ENDIF
371     READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nz)
372     DO K=1,Nz
373     READ(37,*) (eosC(I,K),I=1,9)
374     write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),
375     & (eosC(I,K),I=1,9)
376     ENDDO
377     CLOSE(37)
378     ENDIF
379 cnh 1.1
380     goptCount = 0
381     IF ( usingCartesianGrid ) goptCount = goptCount+1
382     IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
383     IF ( goptCount .NE. 1 ) THEN
384     WRITE(msgBuf,'(A)')
385     & 'S/R INI_PARMS: More than one coordinate system requested'
386     CALL PRINT_ERROR( msgBuf , myThid)
387     STOP 'ABNORMAL END: S/R INI_PARMS'
388     ENDIF
389    
390     _END_MASTER(myThid)
391    
392     C-- Everyone else must wait for the parameters to be loaded
393     _BARRIER
394     C
395    
396     RETURN
397     END
398    

  ViewVC Help
Powered by ViewVC 1.1.22