/[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.14 - (hide annotations) (download)
Mon Jun 8 21:43:01 1998 UTC (26 years ago) by cnh
Branch: MAIN
CVS Tags: checkpoint6
Changes since 1.13: +50 -5 lines
Merge of GM Redi and spherical polar and inplicit diffusion
and CD. Everything for a global run is now included, however,
still some discrepancies with GM Redi.

1 cnh 1.14 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_parms.F,v 1.11 1998/05/28 16:19:50 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.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 cnh 1.14 metricTerms = .TRUE.
181 adcroft 1.12 implicitDiffusion = .FALSE.
182 cnh 1.1 READ(UNIT=iUnit,NML=PARM01,IOSTAT=errIO,err=3)
183     IF ( errIO .GE. 0 ) GOTO 4
184     3 CONTINUE
185     WRITE(msgBuf,'(A)')
186     & 'S/R INI_PARMS'
187     CALL PRINT_ERROR( msgBuf , 1)
188     WRITE(msgBuf,'(A)')
189     & 'Error reading numerical model '
190     CALL PRINT_ERROR( msgBuf , 1)
191     WRITE(msgBuf,'(A)')
192     & 'parameter file "data"'
193     CALL PRINT_ERROR( msgBuf , 1)
194     WRITE(msgBuf,'(A)')
195     & 'Problem in namelist PARM01'
196     CALL PRINT_ERROR( msgBuf , 1)
197     CALL MODELDATA_EXAMPLE( myThid )
198     STOP 'ABNORMAL END: S/R INI_PARMS'
199     4 CONTINUE
200 cnh 1.8 IF ( implicitFreeSurface ) freeSurfFac = 1. _d 0
201     IF ( rigidLid ) freeSurfFac = 0. _d 0
202 cnh 1.9 IF ( momViscosity ) THEN
203     vfFacMom = 1. _d 0
204     ELSE
205     vfFacMom = 0. _d 0
206     ENDIF
207     IF ( momAdvection ) THEN
208     afFacMom = 1. _d 0
209     ELSE
210     afFacMom = 0. _d 0
211     ENDIF
212     IF ( momForcing ) THEN
213     foFacMom = 1. _d 0
214     ELSE
215     foFacMom = 0. _d 0
216     ENDIF
217     IF ( useCoriolis ) THEN
218     cfFacMom = 1. _d 0
219     ELSE
220     cfFacMom = 0. _d 0
221     ENDIF
222     IF ( momPressureForcing ) THEN
223     pfFacMom = 1. _d 0
224     ELSE
225     pfFacMom = 0. _d 0
226     ENDIF
227 cnh 1.14 IF ( metricTerms ) THEN
228     mTFacMom = 1. _d 0
229     ELSE
230     mTFacMom = 1. _d 0
231     ENDIF
232 cnh 1.8
233     IF ( implicitFreeSurface .AND. rigidLid ) THEN
234     WRITE(msgBuf,'(A)')
235     & 'S/R INI_PARMS: Cannot select implicitFreeSurface and rigidLid.'
236     CALL PRINT_ERROR( msgBuf , myThid)
237     STOP 'ABNORMAL END: S/R INI_PARMS'
238     ENDIF
239 cnh 1.1
240     C-- Elliptic solver parameters
241     cg2dMaxIters = 150
242     cg2dTargetResidual = 1. _d -7
243     cg2dChkResFreq = 1
244 cnh 1.7 cg2dpcOffDFac = 0.51 _d 0
245 cnh 1.1 READ(UNIT=iUnit,NML=PARM02,IOSTAT=errIO,err=5)
246     IF ( errIO .GE. 0 ) GOTO 6
247     5 CONTINUE
248     WRITE(msgBuf,'(A)')
249     & 'S/R INI_PARMS'
250     CALL PRINT_ERROR( msgBuf , 1)
251     WRITE(msgBuf,'(A)')
252     & 'Error reading numerical model '
253     CALL PRINT_ERROR( msgBuf , 1)
254     WRITE(msgBuf,'(A)')
255     & 'parameter file "data".'
256     CALL PRINT_ERROR( msgBuf , 1)
257     WRITE(msgBuf,'(A)')
258     & 'Problem in namelist PARM02'
259     CALL PRINT_ERROR( msgBuf , 1)
260     CALL MODELDATA_EXAMPLE( myThid )
261     STOP 'ABNORMAL END: S/R INI_PARMS'
262     6 CONTINUE
263    
264     C-- Time stepping parameters
265     startTime = 0.
266 cnh 1.4 nTimeSteps = 0
267     endTime = 0.
268 cnh 1.1 nIter0 = 0
269 cnh 1.4 deltaT = 0.
270 cnh 1.7 deltaTClock = 0.
271 cnh 1.4 deltaTtracer = 0.
272     deltaTMom = 0.
273 cnh 1.1 abEps = 0.01
274 cnh 1.7 pchkPtFreq = 0.
275 cnh 1.1 chkPtFreq = 3600.*25
276     dumpFreq = 3600.*100
277 cnh 1.7 writeStatePrec = precFloat32
278     nCheckLev = 1
279     checkPtSuff(1) = 'ckptA'
280     checkPtSuff(2) = 'ckptB'
281 cnh 1.9 cAdjFreq = -1. _d 0
282 cnh 1.14 rCD = -1. _d 0
283     tauCD = 0. _d 0
284 cnh 1.1 READ(UNIT=iUnit,NML=PARM03,IOSTAT=errIO,err=7)
285     IF ( errIO .GE. 0 ) GOTO 8
286     7 CONTINUE
287     WRITE(msgBuf,'(A)')
288     & 'S/R INI_PARMS'
289     CALL PRINT_ERROR( msgBuf , 1)
290     WRITE(msgBuf,'(A)')
291     & 'Error reading numerical model '
292     CALL PRINT_ERROR( msgBuf , 1)
293     WRITE(msgBuf,'(A)')
294     & 'parameter file "data"'
295     CALL PRINT_ERROR( msgBuf , 1)
296     WRITE(msgBuf,'(A)')
297     & 'Problem in namelist PARM03'
298     CALL PRINT_ERROR( msgBuf , 1)
299     CALL MODELDATA_EXAMPLE( myThid )
300     STOP 'ABNORMAL END: S/R INI_PARMS'
301     8 CONTINUE
302 cnh 1.4 C Process "timestepping" params
303     C o Time step size
304     IF ( deltaT .EQ. 0. ) deltaT = deltaTmom
305     IF ( deltaT .EQ. 0. ) deltaT = deltaTtracer
306     IF ( deltaTmom .EQ. 0. ) deltaTmom = deltaT
307     IF ( deltaTtracer .EQ. 0. ) deltaTtracer = deltaT
308 cnh 1.7 IF ( deltaTClock .EQ. 0. ) deltaTClock = deltaT
309 cnh 1.9 C o Convection frequency
310     IF ( cAdjFreq .LT. 0. ) THEN
311     cAdjFreq = deltaTClock
312     ENDIF
313 cnh 1.14 C o CD coupling
314     IF ( tauCD .EQ. 0. _d 0 ) THEN
315     tauCD = deltaTmom
316     ENDIF
317     IF ( rCD .LT. 0. ) THEN
318     rCD = 1. - deltaTMom/tauCD
319     ENDIF
320 cnh 1.4 C o Time step count
321     IF ( endTime .NE. 0 ) THEN
322 cnh 1.7 IF ( deltaTClock .NE. 0 ) nTimeSteps =
323     & INT((endTime-startTime)/deltaTClock)
324 cnh 1.4 ENDIF
325     C o Finish time
326 cnh 1.7 IF ( endTime .EQ. 0. ) endTime = FLOAT(nTimeSteps)*deltaTClock
327 cnh 1.1
328     C-- Grid parameters
329     C In cartesian coords distances are in metres
330     usingCartesianGrid = .TRUE.
331     DO K =1,Nz
332     delZ(K) = 100. _d 0
333     ENDDO
334     dxSpacing = 20. _d 0 * 1000. _d 0
335     dySpacing = 20. _d 0 * 1000. _d 0
336     DO i=1,Nx
337     delX(i) = dxSpacing
338     ENDDO
339     DO j=1,Ny
340     delY(j) = dySpacing
341     ENDDO
342     C In spherical polar distances are in degrees
343     usingSphericalPolarGrid = .FALSE.
344 cnh 1.14 phiMin = -5.0
345     thetaMin = 0.
346     rSphere = 6370. * 1. _d 3
347     rRsphere = 1. _d 0/rSphere
348 cnh 1.1 IF ( usingSphericalPolarGrid ) THEN
349     dxSpacing = 1.
350     dySpacing = 1.
351     DO I=1,Nx
352     delX(I) = dxSpacing
353     ENDDO
354     DO J=1,Ny
355     delY(J) = dySpacing
356     ENDDO
357     ENDIF
358    
359     READ(UNIT=iUnit,NML=PARM04,IOSTAT=errIO,err=9)
360     IF ( errIO .GE. 0 ) GOTO 10
361     9 CONTINUE
362     WRITE(msgBuf,'(A)')
363     & 'S/R INI_PARMS'
364     CALL PRINT_ERROR( msgBuf , 1)
365     WRITE(msgBuf,'(A)')
366     & 'Error reading numerical model '
367     CALL PRINT_ERROR( msgBuf , 1)
368     WRITE(msgBuf,'(A)')
369     & 'parameter file "data"'
370     CALL PRINT_ERROR( msgBuf , 1)
371     WRITE(msgBuf,'(A)')
372     & 'Problem in namelist PARM04'
373     CALL PRINT_ERROR( msgBuf , 1)
374     CALL MODELDATA_EXAMPLE( myThid )
375     STOP 'ABNORMAL END: S/R INI_PARMS'
376     10 CONTINUE
377 adcroft 1.11
378 cnh 1.14 IF ( rSphere .NE. 0 ) THEN
379     rRSphere = 1. _d 0/rSphere
380     ELSE
381     rRSphere = 0.
382     ENDIF
383    
384 adcroft 1.11 C Initialize EOS coefficients (3rd order polynomial)
385     IF (eostype.eq.'POLY3') THEN
386     OPEN(37,FILE='POLY3.COEFFS',STATUS='OLD',FORM='FORMATTED')
387     READ(37,*) I
388     IF (I.NE.Nz) THEN
389     WRITE(0,*) 'ini_parms: attempt to read POLY3.COEFFS failed'
390     WRITE(0,*) ' because bad # of levels in data'
391     STOP 'Bad data in POLY3.COEFFS'
392     ENDIF
393     READ(37,*) (eosRefT(K),eosRefS(K),eosSig0(K),K=1,Nz)
394     DO K=1,Nz
395     READ(37,*) (eosC(I,K),I=1,9)
396     write(0,'(i3,13f8.3)') K,eosRefT(K),eosRefS(K),eosSig0(K),
397     & (eosC(I,K),I=1,9)
398     ENDDO
399     CLOSE(37)
400     ENDIF
401 cnh 1.1
402     goptCount = 0
403     IF ( usingCartesianGrid ) goptCount = goptCount+1
404     IF ( usingSphericalPolarGrid ) goptCount = goptCount+1
405     IF ( goptCount .NE. 1 ) THEN
406     WRITE(msgBuf,'(A)')
407     & 'S/R INI_PARMS: More than one coordinate system requested'
408     CALL PRINT_ERROR( msgBuf , myThid)
409     STOP 'ABNORMAL END: S/R INI_PARMS'
410 cnh 1.14 ENDIF
411    
412     IF ( usingCartesianGrid ) THEN
413     usingSphericalPolarMterms = .FALSE.
414     metricTerms = .FALSE.
415     mTFacMom = 0
416    
417     useConstantF = .FALSE.
418     useBetaPlaneF = .FALSE.
419     useSphereF = .TRUE.
420     omega = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )
421     usingSphericalPolarMterms = .TRUE.
422     metricTerms = .TRUE.
423     mTFacMom = 1
424     ENDIF
425     IF ( usingSphericalPolarGrid ) THEN
426     useConstantF = .FALSE.
427     useBetaPlaneF = .FALSE.
428     useSphereF = .TRUE.
429     omega = 2. _d 0 * PI / ( 3600. _d 0 * 24. _d 0 )
430     usingSphericalPolarMterms = .TRUE.
431     metricTerms = .TRUE.
432     mTFacMom = 1
433 cnh 1.1 ENDIF
434    
435     _END_MASTER(myThid)
436    
437     C-- Everyone else must wait for the parameters to be loaded
438     _BARRIER
439     C
440    
441     RETURN
442     END
443    

  ViewVC Help
Powered by ViewVC 1.1.22