/[MITgcm]/MITgcm/pkg/ggl90/ggl90_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/ggl90/ggl90_readparms.F

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


Revision 1.10 - (hide annotations) (download)
Fri Jan 30 02:23:56 2009 UTC (15 years, 3 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61i
Changes since 1.9: +7 -3 lines
A few adjustments

1 dfer 1.10 C $Header: /u/gcmpack/MITgcm/pkg/ggl90/ggl90_readparms.F,v 1.9 2008/10/07 20:20:18 dfer Exp $
2 mlosch 1.1 C $Name: $
3 dfer 1.10
4 mlosch 1.1 #include "GGL90_OPTIONS.h"
5    
6     SUBROUTINE GGL90_READPARMS( myThid )
7     C /==========================================================\
8     C | SUBROUTINE GGL90_READPARMS |
9     C | o Routine to read in file data.ggl90 |
10     C \==========================================================/
11     IMPLICIT NONE
12    
13     C === Global variables ===
14     #include "SIZE.h"
15     #include "EEPARAMS.h"
16     #include "PARAMS.h"
17     #include "GRID.h"
18     #include "GGL90.h"
19    
20     C === Routine arguments ===
21     C myThid - Number of this instance of GGL90_READPARMS
22     INTEGER myThid
23    
24     #ifdef ALLOW_GGL90
25    
26     C === Local variables ===
27     C msgBuf - Informational/error meesage buffer
28     C errIO - IO error flag
29     C iUnit - Work variable for IO unit number
30    
31     CHARACTER*(MAX_LEN_MBUF) msgBuf
32 jmc 1.7 INTEGER errIO, iUnit, iL
33    
34     INTEGER ILNBLNK
35     EXTERNAL ILNBLNK
36 mlosch 1.1
37     C-- GGL90 vertical mixing parameters
38     NAMELIST /GGL90_PARM01/
39     & GGL90dumpFreq, GGL90taveFreq,
40 mlosch 1.2 & GGL90diffTKEh,
41 mlosch 1.1 & GGL90mixingMaps, GGL90writeState,
42     & GGL90ck, GGL90ceps, GGL90alpha, GGL90m2,
43 mlosch 1.3 & GGL90TKEmin, GGL90TKEsurfMin, GGL90TKEbottom,
44 dfer 1.10 & GGL90mixingLengthMin, mxlMaxFlag,
45     & GGL90viscMax, GGL90diffMax, GGL90TKEFile
46 mlosch 1.1 _BEGIN_MASTER(myThid)
47    
48     WRITE(msgBuf,'(A)') ' GGL90_READPARMS: opening data.ggl90'
49     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
50     & SQUEEZE_RIGHT , 1)
51    
52    
53     CALL OPEN_COPY_DATA_FILE(
54     I 'data.ggl90', 'GGL90_READPARMS',
55     O iUnit,
56     I myThid )
57    
58     C-- set default TKE vertical mixing parameters
59     GGL90dumpFreq = dumpFreq
60     GGL90taveFreq = taveFreq
61     GGL90mixingMaps = .FALSE.
62     GGL90writeState = .FALSE.
63     GGL90ck = 0.1 _d 0
64     GGL90ceps = 0.7 _d 0
65     GGL90alpha = 1.0 _d 0
66 mlosch 1.3 C Blanke and Delecluse (1993, JPO) use
67     GGL90m2 = 3.75 _d 0
68 mlosch 1.1 GGL90TKEmin = 1.0 _d -11
69 mlosch 1.3 C Blanke and Delecluse (1993, JPO) use
70     GGL90TKEsurfMin = 1.0 _d -04
71 mlosch 1.1 GGL90TKEbottom = UNSET_RL
72 dfer 1.9 GGL90viscMax = 1. _d 2
73     GGL90diffMax = 1. _d 2
74 mlosch 1.2 GGL90diffTKEh = 0.0 _d 0
75 mlosch 1.1 GGL90mixingLengthMin = 1.0 _d -08
76 dfer 1.10 mxlMaxFlag = 0
77 mlosch 1.1 GGL90TKEFile = ' '
78    
79     C-----------------------------------------------------------------------
80     C define some non-dimensional constants and
81     C the vertical mixing coefficients in m-k-s units
82     C-----------------------------------------------------------------------
83    
84     C-- Read settings from model parameter file "data.ggl90".
85     READ(UNIT=iUnit,NML=GGL90_PARM01,IOSTAT=errIO)
86     IF ( errIO .LT. 0 ) THEN
87     WRITE(msgBuf,'(A)')
88     & 'S/R INI_PARMS'
89     CALL PRINT_ERROR( msgBuf , 1)
90     WRITE(msgBuf,'(A)')
91     & 'Error reading numerical model '
92     CALL PRINT_ERROR( msgBuf , 1)
93     WRITE(msgBuf,'(A)')
94     & 'parameter file "data.ggl90"'
95     CALL PRINT_ERROR( msgBuf , 1)
96     WRITE(msgBuf,'(A)')
97     & 'Problem in namelist GGL90_PARM01'
98     CALL PRINT_ERROR( msgBuf , 1)
99     C CALL MODELDATA_EXAMPLE( myThid )
100     STOP 'ABNORMAL END: S/R GGL90_READPARMS'
101     ENDIF
102    
103     CLOSE(iUnit)
104    
105     WRITE(msgBuf,'(A)')
106     & ' GGL90_READPARMS: finished reading data.ggl90'
107     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
108     & SQUEEZE_RIGHT , 1)
109    
110     C Now set-up any remaining parameters that result from the input parameters
111     IF ( GGL90TKEbottom .EQ. UNSET_RL ) THEN
112     GGL90TKEbottom = GGL90TKEmin
113     ENDIF
114     IF ( GGL90TKEmin .LE. 0. ) THEN
115     WRITE(msgBuf,'(A)')
116     & 'GGL90TKEmin must be greater than zero'
117     CALL PRINT_ERROR( msgBuf , 1)
118     STOP 'ABNORMAL END: S/R GGL90_READPARMS'
119     ENDIF
120     IF ( GGL90TKEbottom .LT. 0. ) THEN
121     WRITE(msgBuf,'(A)')
122     & 'GGL90TKEbottom must not be less than zero'
123     CALL PRINT_ERROR( msgBuf , 1)
124     STOP 'ABNORMAL END: S/R GGL90_READPARMS'
125     ENDIF
126     IF ( GGL90mixingLengthMin .LE. 0. ) THEN
127     WRITE(msgBuf,'(A)')
128     & 'GGL90mixingLengthMin must be greater than zero'
129     CALL PRINT_ERROR( msgBuf , 1)
130     STOP 'ABNORMAL END: S/R GGL90_READPARMS'
131     ENDIF
132     IF ( GGL90viscMax .LE. 0. ) THEN
133     WRITE(msgBuf,'(A)') 'GGL90viscMax must be greater than zero'
134     CALL PRINT_ERROR( msgBuf , 1)
135     STOP 'ABNORMAL END: S/R GGL90_READPARMS'
136     ENDIF
137     IF ( GGL90diffMax .LE. 0. ) THEN
138     WRITE(msgBuf,'(A)') 'GGL90diffMax must be greater than zero'
139     CALL PRINT_ERROR( msgBuf , 1)
140     STOP 'ABNORMAL END: S/R GGL90_READPARMS'
141     ENDIF
142    
143 mlosch 1.4 C-- print TKE vertical mixing parameters to stdout for better debugging
144 mlosch 1.6 WRITE(msgBuf,'(A)')
145     &'// ======================================================='
146     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
147 mlosch 1.4 & SQUEEZE_RIGHT , 1)
148 mlosch 1.6 WRITE(msgBuf,'(A)') '// GGL90 configuration'
149     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
150 mlosch 1.4 & SQUEEZE_RIGHT , 1)
151 mlosch 1.6 WRITE(msgBuf,'(A)')
152     &'// ======================================================='
153 mlosch 1.4 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154 mlosch 1.6 & SQUEEZE_RIGHT , 1)
155    
156     CALL WRITE_0D_R8( GGL90dumpFreq, INDEX_NONE,'GGL90dumpFreq =',
157     &' /* GGL90 state write out interval ( s ). */')
158     CALL WRITE_0D_R8( GGL90taveFreq, INDEX_NONE,'GGL90taveFreq =',
159     &' /* GGL90 averaging interval ( s ). */')
160     CALL WRITE_0D_L(GGL90mixingMaps,INDEX_NONE,
161     & 'GGL90mixingMAPS =', ' /* GGL90 IO flag. */')
162     CALL WRITE_0D_L(GGL90writeState,INDEX_NONE,
163     & 'GGL90writeState =', ' /* GGL90 IO flag. */')
164     CALL WRITE_0D_R8( GGL90ck, INDEX_NONE,'GGL90ck =',
165     &' /* GGL90 viscosity parameter. */')
166     CALL WRITE_0D_R8( GGL90ceps, INDEX_NONE,'GGL90ceps =',
167     &' /* GGL90 dissipation parameter. */')
168     CALL WRITE_0D_R8( GGL90alpha, INDEX_NONE,'GGL90alpha =',
169     &' /* GGL90 TKE diffusivity parameter. */')
170     CALL WRITE_0D_R8( GGL90m2, INDEX_NONE,'GGL90m2 =',
171     &' /* GGL90 wind stress to vertical stress ratio. */')
172     CALL WRITE_0D_R8( GGL90TKEmin, INDEX_NONE,'GGL90TKEmin =',
173     &' /* GGL90 minimum kinetic energy ( m^2/s^2 ). */')
174     CALL WRITE_0D_R8( GGL90TKEsurfMin, INDEX_NONE,
175     & 'GGL90TKEsurfMin =',
176     &' /* GGL90 minimum surface kinetic energy ( m^2/s^2 ). */')
177     CALL WRITE_0D_R8( GGL90TKEbottom, INDEX_NONE,
178     & 'GGL90TKEbottom =',
179     & ' /* GGL90 bottom kinetic energy ( m^2/s^2 ). */')
180     CALL WRITE_0D_R8( GGL90viscMax, INDEX_NONE,'GGL90viscMax =',
181     & ' /* GGL90 upper limit for viscosity ( m^2/s ). */')
182     CALL WRITE_0D_R8( GGL90diffMax, INDEX_NONE,'GGL90diffMax =',
183     & ' /* GGL90 upper limit for diffusivity ( m^2/s ). */')
184     CALL WRITE_0D_R8( GGL90diffTKEh, INDEX_NONE,'GGL90diffTKEh =',
185     & ' /* GGL90 horizontal diffusivity for TKE ( m^2/s ). */')
186     CALL WRITE_0D_R8( GGL90mixingLengthMin, INDEX_NONE,
187     & 'GGL90mixingLengthMin =',
188     & ' /* GGL90 minimum mixing length ( m ). */')
189 dfer 1.10 CALL WRITE_0D_I(mxlMaxFlag, INDEX_NONE, 'mxlMaxFlag =',
190     & ' /* Flag for limiting mixing-length method */')
191 jmc 1.7 iL = MAX_LEN_MBUF - 22
192 jmc 1.8 iL = MIN( iL, MAX(ILNBLNK(GGL90TKEFile),1) )
193 jmc 1.7 WRITE(msgBuf,'(A,A)')'GGL90: GGL90TKEFile = ',GGL90TKEFile(1:iL)
194 mlosch 1.4 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
195     & SQUEEZE_RIGHT , 1)
196 mlosch 1.6
197     WRITE(msgBuf,'(A)')
198     &'// ======================================================='
199     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
200 mlosch 1.4 & SQUEEZE_RIGHT , 1)
201 mlosch 1.6 WRITE(msgBuf,'(A)') '// End of GGL90 config. summary'
202     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
203 mlosch 1.4 & SQUEEZE_RIGHT , 1)
204 mlosch 1.6 WRITE(msgBuf,'(A)')
205     &'// ======================================================='
206 mlosch 1.4 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
207 mlosch 1.6 & SQUEEZE_RIGHT , 1)
208     WRITE(msgBuf,'(A)') ' '
209 mlosch 1.4 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
210 mlosch 1.6 & SQUEEZE_RIGHT , 1)
211 mlosch 1.4
212     _END_MASTER(myThid)
213    
214     C-- Everyone else must wait for the parameters to be loaded
215     _BARRIER
216    
217 mlosch 1.1 #endif /* ALLOW_GGL90 */
218    
219     return
220     end

  ViewVC Help
Powered by ViewVC 1.1.22