/[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.9 - (hide annotations) (download)
Tue Oct 7 20:20:18 2008 UTC (15 years, 7 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint61f, checkpoint61g, checkpoint61e, checkpoint61h
Changes since 1.8: +3 -3 lines
Change default for max visc/diff

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

  ViewVC Help
Powered by ViewVC 1.1.22