/[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 - (hide annotations) (download)
Sun Feb 4 14:38:50 2001 UTC (23 years, 4 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_post, checkpoint43a-release1mods, checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, chkpt44d_post, checkpoint44e_pre, release1_b1, checkpoint43, checkpoint38, release1_chkpt44d_post, checkpoint40pre2, release1-branch_tutorials, chkpt44a_post, checkpoint40pre4, chkpt44c_pre, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, pre38tag1, checkpoint44g_post, release1-branch-end, c37_adj, checkpoint44b_post, pre38-close, checkpoint39, checkpoint37, checkpoint36, checkpoint35, checkpoint40pre5, chkpt44a_pre, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, release1_beta1, checkpoint44b_pre, checkpoint42, checkpoint40, checkpoint41, checkpoint44, chkpt44c_post, checkpoint44f_pre, release1-branch_branchpoint
Branch point for: release1_final, release1-branch, release1, ecco-branch, pre38, release1_coupled
Changes since 1.3: +2 -0 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

1 cnh 1.4 C $Header: $
2     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     C k - Loop counter
30    
31     CHARACTER*(MAX_LEN_MBUF) msgBuf
32     INTEGER errIO, iUnit, k
33    
34     C-- KPP vertical mixing parameters
35     NAMELIST /KPP_PARM01/
36     & kpp_freq, kpp_dumpFreq, kpp_taveFreq,
37     & KPPmixingMaps, KPPwriteState,
38     & minKPPhbl,
39     & epsln, phepsi, epsilon, vonk, dB_dz,
40     & conc1, conam, concm, conc2, zetam,
41     & conas, concs, conc3, zetas,
42     & Ricr, cekman, cmonob, concv, hbf,
43     & zmin, zmax, umin, umax,
44     & num_v_smooth_Ri, num_v_smooth_BV,
45     & num_z_smooth_sh, num_m_smooth_sh,
46     & Riinfty, BVSQcon, difm0, difs0, dift0,
47     & difmcon, difscon, diftcon,
48     & cstar
49    
50     _BEGIN_MASTER(myThid)
51    
52     WRITE(msgBuf,'(A)') ' KPP_INIT: opening data.kpp'
53     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
54     & SQUEEZE_RIGHT , 1)
55    
56    
57     CALL OPEN_COPY_DATA_FILE(
58     I 'data.kpp', 'KPP_INIT',
59     O iUnit,
60     I myThid )
61    
62     C-- set default KPP vertical mixing parameters
63     kpp_freq = deltaTClock
64     kpp_dumpFreq = 0.
65     kpp_taveFreq = 0.
66     KPPmixingMaps = .FALSE.
67     KPPwriteState = .FALSE.
68     minKPPhbl = delZ(1)*0.5
69    
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