/[MITgcm]/MITgcm/pkg/kpp/kpp_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/kpp/kpp_readparms.F

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


Revision 1.4.8.3 - (hide annotations) (download)
Mon Jul 7 16:18:47 2003 UTC (20 years, 11 months ago) by heimbach
Branch: ecco-branch
CVS Tags: ecco_c51_e34d, ecco_c51_e34e, ecco_c51_e34f, ecco_c51_e34g, ecco_c51_e34b, ecco_c51_e34c
Changes since 1.4.8.2: +3 -2 lines
o new parameter maxKPPhbl in KPP

1 heimbach 1.4.8.3 C $Header: /u/gcmpack/MITgcm/pkg/kpp/kpp_readparms.F,v 1.4.8.2 2003/02/13 19:28:38 dimitri Exp $
2 heimbach 1.4.8.1 C $Name: $
3 heimbach 1.1 #include "KPP_OPTIONS.h"
4    
5     SUBROUTINE KPP_READPARMS( myThid )
6     C /==========================================================\
7     C | SUBROUTINE KPP_READPARMS |
8     C | o Routine to read in file data.kpp |
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 "KPP_PARAMS.h"
18    
19     C === Routine arguments ===
20     C myThid - Number of this instance of KPP_INIT
21     INTEGER myThid
22    
23     #ifdef ALLOW_KPP
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 dimitri 1.4.8.2 INTEGER errIO, iUnit
32 heimbach 1.1
33     C-- KPP vertical mixing parameters
34     NAMELIST /KPP_PARM01/
35     & kpp_freq, kpp_dumpFreq, kpp_taveFreq,
36     & KPPmixingMaps, KPPwriteState,
37 heimbach 1.4.8.3 & minKPPhbl, maxKPPhbl,
38 heimbach 1.1 & epsln, phepsi, epsilon, vonk, dB_dz,
39     & conc1, conam, concm, conc2, zetam,
40     & conas, concs, conc3, zetas,
41     & Ricr, cekman, cmonob, concv, hbf,
42     & zmin, zmax, umin, umax,
43     & num_v_smooth_Ri, num_v_smooth_BV,
44     & num_z_smooth_sh, num_m_smooth_sh,
45     & Riinfty, BVSQcon, difm0, difs0, dift0,
46     & difmcon, difscon, diftcon,
47     & cstar
48    
49     _BEGIN_MASTER(myThid)
50    
51     WRITE(msgBuf,'(A)') ' KPP_INIT: opening data.kpp'
52     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
53     & SQUEEZE_RIGHT , 1)
54    
55    
56     CALL OPEN_COPY_DATA_FILE(
57     I 'data.kpp', 'KPP_INIT',
58     O iUnit,
59     I myThid )
60    
61     C-- set default KPP vertical mixing parameters
62     kpp_freq = deltaTClock
63 dimitri 1.4.8.2 kpp_dumpFreq = dumpFreq
64     kpp_taveFreq = taveFreq
65 heimbach 1.1 KPPmixingMaps = .FALSE.
66     KPPwriteState = .FALSE.
67 heimbach 1.4.8.1 minKPPhbl = drF(1)*0.5
68 heimbach 1.4.8.3 maxKPPhbl = drF(1)*0.5
69 heimbach 1.1
70     C-----------------------------------------------------------------------
71     C define some non-dimensional constants and
72     C the vertical mixing coefficients in m-k-s units
73     C-----------------------------------------------------------------------
74    
75     epsln = 1.e-20
76     phepsi = 1.e-10
77     epsilon = 0.1
78     vonk = 0.40
79     dB_dz = 5.2e-5
80     conc1 = 5.0
81     conam = 1.257
82     concm = 8.380
83     conc2 = 16.0
84     zetam = -0.2
85     conas = -28.86
86     concs = 98.96
87     conc3 = 16.0
88     zetas = -1.0
89    
90     c parameters for subroutine "bldepth"
91    
92     Ricr = 0.30
93     cekman = 0.7
94     cmonob = 1.0
95     concv = 1.8
96     hbf = 1.0
97    
98     c parameters and common arrays for subroutines
99     c "kmixinit" and "wscale"
100    
101     zmin = -4.e-7
102     zmax = 0.0
103     umin = 0.0
104     umax = .04
105    
106     c parameters for subroutine "Ri_iwmix"
107    
108     num_v_smooth_Ri = 0
109     num_v_smooth_BV = 0
110     num_z_smooth_sh = 0
111     num_m_smooth_sh = 0
112     Riinfty = 0.7
113     BVSQcon = -0.2e-4
114    
115     difm0 = 0.005
116     difs0 = 0.005
117     dift0 = 0.005
118    
119     difmcon = 0.1
120     difscon = 0.1
121     diftcon = 0.1
122    
123     C parameters for subroutine "blmix"
124    
125     cstar = 10.
126    
127     C-----------------------------------------------------------------------
128    
129     C-- Read settings from model parameter file "data.kpp".
130     READ(UNIT=iUnit,NML=KPP_PARM01,IOSTAT=errIO)
131     IF ( errIO .LT. 0 ) THEN
132     WRITE(msgBuf,'(A)')
133     & 'S/R INI_PARMS'
134     CALL PRINT_ERROR( msgBuf , 1)
135     WRITE(msgBuf,'(A)')
136     & 'Error reading numerical model '
137     CALL PRINT_ERROR( msgBuf , 1)
138     WRITE(msgBuf,'(A)')
139     & 'parameter file "data.kpp"'
140     CALL PRINT_ERROR( msgBuf , 1)
141     WRITE(msgBuf,'(A)')
142     & 'Problem in namelist KPP_PARM01'
143     CALL PRINT_ERROR( msgBuf , 1)
144     C CALL MODELDATA_EXAMPLE( myThid )
145     STOP 'ABNORMAL END: S/R KPP_INIT'
146     ENDIF
147    
148     CLOSE(iUnit)
149    
150     WRITE(msgBuf,'(A)') ' KPP_INIT: finished reading data.kpp'
151     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
152     & SQUEEZE_RIGHT , 1)
153    
154     _END_MASTER(myThid)
155    
156     C-- Everyone else must wait for the parameters to be loaded
157     _BARRIER
158    
159     #endif /* ALLOW_KPP */
160    
161     return
162     end

  ViewVC Help
Powered by ViewVC 1.1.22