/[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.17 - (hide annotations) (download)
Fri Jun 12 19:33:33 1998 UTC (25 years, 11 months ago) by cnh
Branch: MAIN
Changes since 1.16: +2 -1 lines
Chages to make default setup correct for 4 degreee global comparison

1 cnh 1.17 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_parms.F,v 1.16 1998/06/10 16:05:39 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.14 & momPressureForcing, metricTerms,
62 cnh 1.1 & tempDiffusion, tempAdvection, tempForcing,
63 cnh 1.8 & saltDiffusion, saltAdvection, saltForcing,
64 cnh 1.10 & implicitFreeSurface, rigidLid, freeSurfFac,
65 adcroft 1.16 & tempStepping, saltStepping, 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 cnh 1.15 C-- Input files
84     NAMELIST /PARM05/
85     & bathyFile, hydrogThetaFile, hydrogSaltFile,
86     & zonalWindFile, meridWindFile
87    
88 cnh 1.1 C
89     _BEGIN_MASTER(myThid)
90    
91     C-- Open the parameter file
92     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
93     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
94     OPEN(UNIT=modelDataUnit,FILE='data',STATUS='OLD',err=1,IOSTAT=errIO)
95     IF ( errIO .GE. 0 ) GOTO 2
96     1 CONTINUE
97     WRITE(msgBuf,'(A)')
98     & 'S/R INI_PARMS'
99     CALL PRINT_ERROR( msgBuf , 1)
100     WRITE(msgBuf,'(A)')
101     & 'Unable to open model parameter'
102     CALL PRINT_ERROR( msgBuf , 1)
103     WRITE(msgBuf,'(A)')
104     & 'file "data"'
105     CALL PRINT_ERROR( msgBuf , 1)
106     CALL MODELDATA_EXAMPLE( myThid )
107     STOP 'ABNORMAL END: S/R INI_PARMS'
108     2 CONTINUE
109    
110     1000 CONTINUE
111     READ(modelDataUnit,FMT='(A)',END=1001) RECORD
112     IL = MAX(ILNBLNK(RECORD),1)
113     IF ( RECORD(1:1) .NE. commentCharacter )
114     & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
115     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
116     GOTO 1000
117     1001 CONTINUE
118     CLOSE(modelDataUnit)
119    
120     C-- Report contents of model parameter file
121     WRITE(msgBuf,'(A)')
122     &'// ======================================================='
123     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
124     WRITE(msgBuf,'(A)') '// Model parameter file "data"'
125     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
126     WRITE(msgBuf,'(A)')
127     &'// ======================================================='
128     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
129     & SQUEEZE_RIGHT , 1)
130     iUnit = scrUnit2
131     REWIND(iUnit)
132     2000 CONTINUE
133     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
134     IL = MAX(ILNBLNK(RECORD),1)
135     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
136     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
137     GOTO 2000
138     2001 CONTINUE
139     CLOSE(iUnit)
140     WRITE(msgBuf,'(A)') ' '
141     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
142     & SQUEEZE_RIGHT , 1)
143    
144    
145     C-- Read settings from model parameter file "data".
146     iUnit = scrUnit1
147     REWIND(iUnit)
148    
149     C-- Set default "physical" parameters
150     DO K =1,Nz
151     tRef(K) = 30.D0 - FLOAT(K)
152     ENDDO
153     gravity = 9.81 D0
154 cnh 1.8 gBaro = gravity
155 cnh 1.1 rhoNil = 999.8 D0
156     f0=1.D-4
157     beta = 1. _d -11
158     viscAh=1.d3
159 adcroft 1.16 diffKhT=1.0d3
160     diffKhS=1.0d3
161 cnh 1.1 viscAz=1.d-3
162     diffKzT=1.d-5
163 adcroft 1.16 diffKzS=1.d-5
164     viscA4=0.
165 cnh 1.1 diffK4T=0.
166     diffK4S=0.
167 adcroft 1.6 GMmaxslope=1.d-2
168     GMlength=200.d3
169     GMalpha=0.
170     GMdepth=1000.
171     GMkbackground=0.
172 adcroft 1.11 tAlpha=2.d-4
173     sBeta=1.d-5
174 adcroft 1.13 eosType='LINEAR'
175 cnh 1.8 implicitFreeSurface = .TRUE.
176     rigidLid = .FALSE.
177     freeSurfFac = 1. _d 0
178 cnh 1.9 momViscosity = .TRUE.
179     momAdvection = .TRUE.
180     momForcing = .TRUE.
181     useCoriolis = .TRUE.
182     momPressureForcing = .TRUE.
183 cnh 1.10 momStepping = .TRUE.
184     tempStepping = .TRUE.
185 adcroft 1.16 saltStepping = .TRUE.
186 cnh 1.14 metricTerms = .TRUE.
187 adcroft 1.12 implicitDiffusion = .FALSE.
188 cnh 1.1 READ(UNIT=iUnit,NML=PARM01,IOSTAT=errIO,err=3)
189     IF ( errIO .GE. 0 ) GOTO 4
190     3 CONTINUE
191     WRITE(msgBuf,'(A)')
192     & 'S/R INI_PARMS'
193     CALL PRINT_ERROR( msgBuf , 1)
194     WRITE(msgBuf,'(A)')
195     & 'Error reading numerical model '
196     CALL PRINT_ERROR( msgBuf , 1)
197     WRITE(msgBuf,'(A)')
198     & 'parameter file "data"'
199     CALL PRINT_ERROR( msgBuf , 1)
200     WRITE(msgBuf,'(A)')
201     & 'Problem in namelist PARM01'
202     CALL PRINT_ERROR( msgBuf , 1)
203     CALL MODELDATA_EXAMPLE( myThid )
204     STOP 'ABNORMAL END: S/R INI_PARMS'
205     4 CONTINUE
206 cnh 1.8 IF ( implicitFreeSurface ) freeSurfFac = 1. _d 0
207     IF ( rigidLid ) freeSurfFac = 0. _d 0
208 cnh 1.9 IF ( momViscosity ) THEN
209     vfFacMom = 1. _d 0
210     ELSE
211     vfFacMom = 0. _d 0
212     ENDIF
213     IF ( momAdvection ) THEN
214     afFacMom = 1. _d 0
215     ELSE
216     afFacMom = 0. _d 0
217     ENDIF
218     IF ( momForcing ) THEN
219     foFacMom = 1. _d 0
220     ELSE
221     foFacMom = 0. _d 0
222     ENDIF
223     IF ( useCoriolis ) THEN
224     cfFacMom = 1. _d 0
225     ELSE
226     cfFacMom = 0. _d 0
227     ENDIF
228     IF ( momPressureForcing ) THEN
229     pfFacMom = 1. _d 0
230     ELSE
231     pfFacMom = 0. _d 0
232     ENDIF
233 cnh 1.14 IF ( metricTerms ) THEN
234     mTFacMom = 1. _d 0
235     ELSE
236     mTFacMom = 1. _d 0
237     ENDIF
238 cnh 1.8
239     IF ( implicitFreeSurface .AND. rigidLid ) THEN
240     WRITE(msgBuf,'(A)')
241     & 'S/R INI_PARMS: Cannot select implicitFreeSurface and rigidLid.'
242     CALL PRINT_ERROR( msgBuf , myThid)
243     STOP 'ABNORMAL END: S/R INI_PARMS'
244     ENDIF
245 cnh 1.1
246     C-- Elliptic solver parameters
247     cg2dMaxIters = 150
248     cg2dTargetResidual = 1. _d -7
249     cg2dChkResFreq = 1
250 cnh 1.7 cg2dpcOffDFac = 0.51 _d 0
251 cnh 1.1 READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)
252     IF ( errIO .GE. 0 ) GOTO 6
253     5 CONTINUE
254     WRITE(msgBuf,'(A)')
255     & 'S/R INI_PARMS'
256     CALL PRINT_ERROR( msgBuf , 1)
257     WRITE(msgBuf,'(A)')
258     & 'Error reading numerical model '
259     CALL PRINT_ERROR( msgBuf , 1)
260     WRITE(msgBuf,'(A)')
261     & 'parameter file "data".'
262     CALL PRINT_ERROR( msgBuf , 1)
263     WRITE(msgBuf,'(A)')
264     & 'Problem in namelist PARM02'
265     CALL PRINT_ERROR( msgBuf , 1)
266     CALL MODELDATA_EXAMPLE( myThid )
267     STOP 'ABNORMAL END: S/R INI_PARMS'
268     6 CONTINUE
269    
270     C-- Time stepping parameters
271     startTime = 0.
272 cnh 1.4 nTimeSteps = 0
273     endTime = 0.
274 cnh 1.1 nIter0 = 0
275 cnh 1.4 deltaT = 0.
276 cnh 1.7 deltaTClock = 0.
277 cnh 1.4 deltaTtracer = 0.
278     deltaTMom = 0.
279 cnh 1.1 abEps = 0.01
280 cnh 1.7 pchkPtFreq = 0.
281 cnh 1.1 chkPtFreq = 3600.*25
282     dumpFreq = 3600.*100
283 cnh 1.7 writeStatePrec = precFloat32
284     nCheckLev = 1
285     checkPtSuff(1) = 'ckptA'
286     checkPtSuff(2) = 'ckptB'
287 cnh 1.9 cAdjFreq = -1. _d 0
288 cnh 1.14 rCD = -1. _d 0
289     tauCD = 0. _d 0
290 cnh 1.1 READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)
291     IF ( errIO .GE. 0 ) GOTO 8
292     7 CONTINUE
293     WRITE(msgBuf,'(A)')
294     & 'S/R INI_PARMS'
295     CALL PRINT_ERROR( msgBuf , 1)
296     WRITE(msgBuf,'(A)')
297     & 'Error reading numerical model '
298     CALL PRINT_ERROR( msgBuf , 1)
299     WRITE(msgBuf,'(A)')
300     & 'parameter file "data"'
301     CALL PRINT_ERROR( msgBuf , 1)
302     WRITE(msgBuf,'(A)')
303     & 'Problem in namelist PARM03'
304     CALL PRINT_ERROR( msgBuf , 1)
305     CALL MODELDATA_EXAMPLE( myThid )
306     STOP 'ABNORMAL END: S/R INI_PARMS'
307     8 CONTINUE
308 cnh 1.4 C Process "timestepping" params
309     C o Time step size
310     IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
311     IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
312     IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
313     IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
314 cnh 1.7 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
315 cnh 1.9 C o Convection frequency
316     IF ( cAdjFreq .LT. 0. ) THEN
317     cAdjFreq = deltaTClock
318     ENDIF
319 cnh 1.14 C o CD coupling
320     IF ( tauCD .EQ. 0. _d 0 ) THEN
321     tauCD = deltaTmom
322     ENDIF
323     IF ( rCD .LT. 0. ) THEN
324     rCD = 1. - deltaTMom/tauCD
325     ENDIF
326 cnh 1.4 C o Time step count
327     IF ( endTime .NE. 0 ) THEN
328 cnh 1.7 IF ( deltaTClock .NE. 0 ) nTimeSteps =
329     & INT((endTime-startTime)/deltaTClock)
330 cnh 1.4 ENDIF
331     C o Finish time
332 cnh 1.7 IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock
333 cnh 1.1
334     C-- Grid parameters
335     C In cartesian coords distances are in metres
336     usingCartesianGrid = .TRUE.
337     DO K =1,Nz
338     delZ(K) = 100. _d 0
339     ENDDO
340     dxSpacing = 20. _d 0 * 1000. _d 0
341     dySpacing = 20. _d 0 * 1000. _d 0
342     DO i=1,Nx
343     delX(i) = dxSpacing
344     ENDDO
345     DO j=1,Ny
346     delY(j) = dySpacing
347     ENDDO
348     C In spherical polar distances are in degrees
349     usingSphericalPolarGrid = .FALSE.
350 cnh 1.14 phiMin = -5.0
351     thetaMin = 0.
352     rSphere = 6370. * 1. _d 3
353     rRsphere = 1. _d 0/rSphere
354 cnh 1.1 IF ( usingSphericalPolarGrid ) THEN
355     dxSpacing = 1.
356     dySpacing = 1.
357     DO I=1,Nx
358     delX(I) = dxSpacing
359     ENDDO
360     DO J=1,Ny
361     delY(J) = dySpacing
362     ENDDO
363     ENDIF
364    
365     READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO,err=9)
366     IF ( errIO .GE. 0 ) GOTO 10
367     9 CONTINUE
368     WRITE(msgBuf,'(A)')
369     & 'S/R INI_PARMS'
370     CALL PRINT_ERROR( msgBuf , 1)
371     WRITE(msgBuf,'(A)')
372     & 'Error reading numerical model '
373     CALL PRINT_ERROR( msgBuf , 1)
374     WRITE(msgBuf,'(A)')
375     & 'parameter file "data"'
376     CALL PRINT_ERROR( msgBuf , 1)
377     WRITE(msgBuf,'(A)')
378     & 'Problem in namelist PARM04'
379     CALL PRINT_ERROR( msgBuf , 1)
380     CALL MODELDATA_EXAMPLE( myThid )
381     STOP 'ABNORMAL END: S/R INI_PARMS'
382     10 CONTINUE
383 adcroft 1.11
384 cnh 1.14 IF ( rSphere .NE. 0 ) THEN
385     rRSphere = 1. _d 0/rSphere
386     ELSE
387     rRSphere = 0.
388     ENDIF
389    
390 adcroft 1.11 C Initialize EOS coefficients (3rd order polynomial)
391     IF (eostype.eq.'POLY3') THEN
392     OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
393     READ(37,*) I
394     IF (I.NE.Nz) THEN
395     WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'
396     WRITE(0,*) ' because bad # of levels in data'
397     STOP 'Bad data in POLY3.COEFFS'
398     ENDIF
399     READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nz)
400     DO K=1,Nz
401     READ(37,*) (eosC(I,K),I=1,9)
402     write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),
403     & (eosC(I,K),I=1,9)
404     ENDDO
405     CLOSE(37)
406     ENDIF
407 cnh 1.1
408     goptCount = 0
409     IF ( usingCartesianGrid ) goptCount = goptCount+1
410     IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
411     IF ( goptCount .NE. 1 ) THEN
412     WRITE(msgBuf,'(A)')
413     & 'S/R INI_PARMS: More than one coordinate system requested'
414     CALL PRINT_ERROR( msgBuf , myThid)
415     STOP 'ABNORMAL END: S/R INI_PARMS'
416 cnh 1.14 ENDIF
417    
418     IF ( usingCartesianGrid ) THEN
419     usingSphericalPolarMterms = .FALSE.
420     metricTerms = .FALSE.
421     mTFacMom = 0
422    
423     useConstantF = .FALSE.
424     useBetaPlaneF = .FALSE.
425     useSphereF = .TRUE.
426     omega = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )
427     usingSphericalPolarMterms = .TRUE.
428     metricTerms = .TRUE.
429     mTFacMom = 1
430     ENDIF
431     IF ( usingSphericalPolarGrid ) THEN
432     useConstantF = .FALSE.
433     useBetaPlaneF = .FALSE.
434     useSphereF = .TRUE.
435     omega = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )
436     usingSphericalPolarMterms = .TRUE.
437     metricTerms = .TRUE.
438     mTFacMom = 1
439 cnh 1.17
440 cnh 1.1 ENDIF
441 cnh 1.15
442     C-- Input files
443     bathyFile = ' '
444     hydrogSaltFile = ' '
445     hydrogThetaFile = ' '
446     zonalWindFile = ' '
447     meridWindFile = ' '
448     READ(UNIT=iUnit,NML=PARM05,IOSTAT=errIO,err=11)
449     IF ( errIO .GE. 0 ) GOTO 12
450     11 CONTINUE
451     WRITE(msgBuf,'(A)')
452     & 'S/R INI_PARMS'
453     CALL PRINT_ERROR( msgBuf , 1)
454     WRITE(msgBuf,'(A)')
455     & 'Error reading numerical model '
456     CALL PRINT_ERROR( msgBuf , 1)
457     WRITE(msgBuf,'(A)')
458     & 'parameter file "data"'
459     CALL PRINT_ERROR( msgBuf , 1)
460     WRITE(msgBuf,'(A)')
461     & 'Problem in namelist PARM05'
462     CALL PRINT_ERROR( msgBuf , 1)
463     CALL MODELDATA_EXAMPLE( myThid )
464     STOP 'ABNORMAL END: S/R INI_PARMS'
465     12 CONTINUE
466 cnh 1.1
467     _END_MASTER(myThid)
468    
469     C-- Everyone else must wait for the parameters to be loaded
470     _BARRIER
471     C
472    
473     RETURN
474     END
475    

  ViewVC Help
Powered by ViewVC 1.1.22