/[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.6 - (hide annotations) (download)
Thu Jun 8 00:12:45 2006 UTC (17 years, 11 months ago) by mlosch
Branch: MAIN
Changes since 1.5: +55 -43 lines
 fix sloppy output

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

  ViewVC Help
Powered by ViewVC 1.1.22