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

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

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

revision 1.5 by jmc, Wed Jun 7 16:34:24 2006 UTC revision 1.11 by jmc, Tue Apr 28 23:27:24 2009 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4  #include "GGL90_OPTIONS.h"  #include "GGL90_OPTIONS.h"
5    
6        SUBROUTINE GGL90_READPARMS( myThid )        SUBROUTINE GGL90_READPARMS( myThid )
7  C     /==========================================================\  C     *==========================================================*
8  C     | SUBROUTINE GGL90_READPARMS                               |  C     | SUBROUTINE GGL90_READPARMS                               |
9  C     | o Routine to read in file data.ggl90                     |  C     | o Routine to read in file data.ggl90                     |
10  C     \==========================================================/  C     *==========================================================*
11        IMPLICIT NONE        IMPLICIT NONE
12    
13  C     === Global variables ===  C     === Global variables ===
# Line 28  C     errIO       - IO error flag Line 29  C     errIO       - IO error flag
29  C     iUnit       - Work variable for IO unit number  C     iUnit       - Work variable for IO unit number
30    
31        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
32        INTEGER errIO, iUnit        INTEGER errIO, iUnit, iL
33    
34          INTEGER  ILNBLNK
35          EXTERNAL ILNBLNK
36    
37  C--   GGL90 vertical mixing parameters  C--   GGL90 vertical mixing parameters
38        NAMELIST /GGL90_PARM01/        NAMELIST /GGL90_PARM01/
# Line 37  C--   GGL90 vertical mixing parameters Line 41  C--   GGL90 vertical mixing parameters
41       &     GGL90mixingMaps, GGL90writeState,       &     GGL90mixingMaps, GGL90writeState,
42       &     GGL90ck, GGL90ceps, GGL90alpha, GGL90m2,       &     GGL90ck, GGL90ceps, GGL90alpha, GGL90m2,
43       &     GGL90TKEmin, GGL90TKEsurfMin, GGL90TKEbottom,       &     GGL90TKEmin, GGL90TKEsurfMin, GGL90TKEbottom,
44       &     GGL90mixingLengthMin, GGL90viscMax, GGL90diffMax,       &     GGL90mixingLengthMin, mxlMaxFlag,
45       &     GGL90TKEFile       &     GGL90viscMax, GGL90diffMax, GGL90TKEFile
46        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
47    
48        WRITE(msgBuf,'(A)') ' GGL90_READPARMS: opening data.ggl90'        WRITE(msgBuf,'(A)') ' GGL90_READPARMS: opening data.ggl90'
# Line 65  C     Blanke and Delecluse (1993, JPO) u Line 69  C     Blanke and Delecluse (1993, JPO) u
69  C     Blanke and Delecluse (1993, JPO) use  C     Blanke and Delecluse (1993, JPO) use
70        GGL90TKEsurfMin      = 1.0 _d -04        GGL90TKEsurfMin      = 1.0 _d -04
71        GGL90TKEbottom       = UNSET_RL        GGL90TKEbottom       = UNSET_RL
72        GGL90viscMax         = 1.0 _d 0        GGL90viscMax         = 1. _d 2
73        GGL90diffMax         = 1.0 _d 1        GGL90diffMax         = 1. _d 2
74        GGL90diffTKEh        = 0.0 _d 0        GGL90diffTKEh        = 0.0 _d 0
75        GGL90mixingLengthMin = 1.0 _d -08        GGL90mixingLengthMin = 1.0 _d -08
76          mxlMaxFlag           = 0
77        GGL90TKEFile         = ' '        GGL90TKEFile         = ' '
78    
79  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
80  C define some non-dimensional constants and  C define some non-dimensional constants and
81  C the vertical mixing coefficients in m-k-s units  C the vertical mixing coefficients in m-k-s units
82  C-----------------------------------------------------------------------  C-----------------------------------------------------------------------
83    
84  C--   Read settings from model parameter file "data.ggl90".  C--   Read settings from model parameter file "data.ggl90".
85        READ(UNIT=iUnit,NML=GGL90_PARM01,IOSTAT=errIO)        READ(UNIT=iUnit,NML=GGL90_PARM01,IOSTAT=errIO)
86        IF ( errIO .LT. 0 ) THEN        IF ( errIO .LT. 0 ) THEN
# Line 102  C      CALL MODELDATA_EXAMPLE( myThid ) Line 107  C      CALL MODELDATA_EXAMPLE( myThid )
107        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
108       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
109    
110  C Now set-up any remaining parameters that result from the input parameters  C Now set-up any remaining parameters that result from the input parameters
111        IF ( GGL90TKEbottom .EQ. UNSET_RL ) THEN        IF ( GGL90TKEbottom .EQ. UNSET_RL ) THEN
112         GGL90TKEbottom = GGL90TKEmin         GGL90TKEbottom = GGL90TKEmin
113        ENDIF        ENDIF
114        IF ( GGL90TKEmin .LE. 0. ) THEN        IF ( GGL90TKEmin .LE. 0. ) THEN
115         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
116       &      'GGL90TKEmin must be greater than zero'       &      'GGL90TKEmin must be greater than zero'
117         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
118         STOP 'ABNORMAL END: S/R GGL90_READPARMS'         STOP 'ABNORMAL END: S/R GGL90_READPARMS'
119        ENDIF        ENDIF
120        IF ( GGL90TKEbottom .LT. 0. ) THEN        IF ( GGL90TKEbottom .LT. 0. ) THEN
121         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
122       &      'GGL90TKEbottom must not be less than zero'       &      'GGL90TKEbottom must not be less than zero'
123         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
124         STOP 'ABNORMAL END: S/R GGL90_READPARMS'         STOP 'ABNORMAL END: S/R GGL90_READPARMS'
125        ENDIF        ENDIF
126        IF ( GGL90mixingLengthMin .LE. 0. ) THEN        IF ( GGL90mixingLengthMin .LE. 0. ) THEN
127         WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
128       &      'GGL90mixingLengthMin must be greater than zero'       &      'GGL90mixingLengthMin must be greater than zero'
129         CALL PRINT_ERROR( msgBuf , 1)         CALL PRINT_ERROR( msgBuf , 1)
130         STOP 'ABNORMAL END: S/R GGL90_READPARMS'         STOP 'ABNORMAL END: S/R GGL90_READPARMS'
# Line 135  C Now set-up any remaining parameters th Line 140  C Now set-up any remaining parameters th
140         STOP 'ABNORMAL END: S/R GGL90_READPARMS'         STOP 'ABNORMAL END: S/R GGL90_READPARMS'
141        ENDIF        ENDIF
142    
 #ifdef UNSAFE_INTERNAL_WRITE  
143  C--   print TKE vertical mixing parameters to stdout for better debugging  C--   print TKE vertical mixing parameters to stdout for better debugging
144        WRITE(msgBuf,*) 'GGL90: GGL90dumpFreq        = ', GGL90dumpFreq        WRITE(msgBuf,'(A)')
145        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,       &'// ======================================================='
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90taveFreq        = ', GGL90taveFreq  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90mixingMaps      = ', GGL90mixingMaps  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90writeState      = ', GGL90writeState  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90ck              = ', GGL90ck  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90ceps            = ', GGL90ceps  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90alpha           = ', GGL90alpha  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90m2              = ', GGL90m2  
       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,  
      &                    SQUEEZE_RIGHT , 1)  
       WRITE(msgBuf,*) 'GGL90: GGL90TKEmin          = ', GGL90TKEmin  
146        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
147       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
148        WRITE(msgBuf,*) 'GGL90: GGL90TKEsurfMin      = ', GGL90TKEsurfMin        WRITE(msgBuf,'(A)') '// GGL90 configuration'
149        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
150       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
151        WRITE(msgBuf,*) 'GGL90: GGL90TKEbottom       = ', GGL90TKEbottom        WRITE(msgBuf,'(A)')
152         &'// ======================================================='
153        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154       &                    SQUEEZE_RIGHT , 1)       &  SQUEEZE_RIGHT , 1)
155        WRITE(msgBuf,*) 'GGL90: GGL90viscMax         = ', GGL90viscMax  
156          CALL WRITE_0D_RL( GGL90dumpFreq, INDEX_NONE,'GGL90dumpFreq =',
157         &'   /* GGL90 state write out interval ( s ). */')
158          CALL WRITE_0D_RL( 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_RL( GGL90ck, INDEX_NONE,'GGL90ck =',
165         &'   /* GGL90 viscosity parameter. */')
166          CALL WRITE_0D_RL( GGL90ceps, INDEX_NONE,'GGL90ceps =',
167         &'   /* GGL90 dissipation parameter. */')
168          CALL WRITE_0D_RL( GGL90alpha, INDEX_NONE,'GGL90alpha =',
169         &'   /* GGL90 TKE diffusivity parameter. */')
170          CALL WRITE_0D_RL( GGL90m2, INDEX_NONE,'GGL90m2 =',
171         &'   /* GGL90 wind stress to vertical stress ratio. */')
172          CALL WRITE_0D_RL( GGL90TKEmin, INDEX_NONE,'GGL90TKEmin =',
173         &'   /* GGL90 minimum kinetic energy ( m^2/s^2 ). */')
174          CALL WRITE_0D_RL( GGL90TKEsurfMin, INDEX_NONE,
175         &     'GGL90TKEsurfMin =',
176         &'   /* GGL90 minimum surface kinetic energy ( m^2/s^2 ). */')
177          CALL WRITE_0D_RL( GGL90TKEbottom, INDEX_NONE,
178         &     'GGL90TKEbottom =',
179         &     '   /* GGL90 bottom kinetic energy ( m^2/s^2 ). */')
180          CALL WRITE_0D_RL( GGL90viscMax, INDEX_NONE,'GGL90viscMax =',
181         &     '   /* GGL90 upper limit for viscosity ( m^2/s ). */')
182          CALL WRITE_0D_RL( GGL90diffMax, INDEX_NONE,'GGL90diffMax =',
183         &     '   /* GGL90 upper limit for diffusivity ( m^2/s ). */')
184          CALL WRITE_0D_RL( GGL90diffTKEh, INDEX_NONE,'GGL90diffTKEh =',
185         &     '   /* GGL90 horizontal diffusivity for TKE ( m^2/s ). */')
186          CALL WRITE_0D_RL( GGL90mixingLengthMin, INDEX_NONE,
187         &     'GGL90mixingLengthMin =',
188         &     '   /* GGL90 minimum mixing length ( m ). */')
189          CALL WRITE_0D_I(mxlMaxFlag, INDEX_NONE, 'mxlMaxFlag =',
190         &     '   /* Flag for limiting mixing-length method */')
191          iL = MAX_LEN_MBUF - 22
192          iL = MIN( iL, MAX(ILNBLNK(GGL90TKEFile),1) )
193          WRITE(msgBuf,'(A,A)')'GGL90: GGL90TKEFile = ',GGL90TKEFile(1:iL)
194        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
195       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
196        WRITE(msgBuf,*) 'GGL90: GGL90diffMax         = ', GGL90diffMax  
197          WRITE(msgBuf,'(A)')
198         &'// ======================================================='
199        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
200       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
201        WRITE(msgBuf,*) 'GGL90: GGL90diffTKEh        = ', GGL90diffTKEh        WRITE(msgBuf,'(A)') '// End of GGL90 config. summary'
202        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
203       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
204        WRITE(msgBuf,*) 'GGL90: GGL90mixingLengthMin = ',        WRITE(msgBuf,'(A)')
205       &                                           GGL90mixingLengthMin       &'// ======================================================='
206        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
207       &                    SQUEEZE_RIGHT , 1)       &  SQUEEZE_RIGHT , 1)
208        WRITE(msgBuf,*) 'GGL90: GGL90TKEFile         = ', GGL90TKEFile        WRITE(msgBuf,'(A)') ' '
209        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
210       &                    SQUEEZE_RIGHT , 1)       &  SQUEEZE_RIGHT , 1)
 #endif /* UNSAFE_INTERNAL_WRITE */  
211    
212        _END_MASTER(myThid)        _END_MASTER(myThid)
213    

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22