/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/streamice_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/dgoldberg/streamice/streamice_readparms.F

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


Revision 1.13 - (hide annotations) (download)
Sat Apr 6 17:43:41 2013 UTC (12 years, 3 months ago) by dgoldberg
Branch: MAIN
Changes since 1.12: +5 -2 lines
use PETSc solver for matrix

1 dgoldberg 1.13 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_readparms.F,v 1.12 2013/03/07 15:23:19 dgoldberg Exp $
2 heimbach 1.1 C $Name: $
3    
4    
5     C this needs changes
6    
7     #include "STREAMICE_OPTIONS.h"
8    
9     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
10     CBOP 0
11     SUBROUTINE STREAMICE_READPARMS( myThid )
12    
13     C !DESCRIPTION:
14     C Initialize STREAMICE variables and constants.
15    
16     C !USES:
17     IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "STREAMICE.h"
22     #include "STREAMICE_BDRY.h"
23    
24     C !INPUT PARAMETERS:
25     INTEGER myThid
26     CEOP
27    
28     #ifdef ALLOW_STREAMICE
29    
30     C !LOCAL VARIABLES:
31     C msgBuf :: Informational/error message buffer
32     C iUnit :: Work variable for IO unit number
33     CHARACTER*(MAX_LEN_MBUF) msgBuf
34     INTEGER iUnit
35    
36     NAMELIST /STREAMICE_PARM01/
37     & streamice_density, streamice_density_ocean_avg,
38 dgoldberg 1.12 & B_glen_isothermal, n_glen, eps_glen_min, eps_u_min,
39 heimbach 1.1 & C_basal_fric_const, n_basal_friction,
40     & streamice_vel_update,streamice_cg_tol,streamice_nonlin_tol,
41 dgoldberg 1.5 & streamice_nonlin_tol_fp,
42 heimbach 1.1 & streamice_max_cg_iter, streamice_max_nl_iter,
43     & STREAMICE_GL_regularize,
44     & STREAMICEthickInit,
45 dgoldberg 1.6 & STREAMICEsigcoordInit,
46     & STREAMICEsigcoordFile,
47 heimbach 1.1 & STREAMICEthickFile,
48     & STREAMICEcalveMaskFile,
49 dgoldberg 1.12 & STREAMICEcostMaskFile,
50 heimbach 1.1 & STREAMICEison,
51     & STREAMICE_dump_mdsio, STREAMICE_tave_mdsio,
52     & STREAMICE_dump_mnc, STREAMICE_tave_mnc,
53     & STREAMICE_GL_regularize, STREAMICE_move_front,
54     & STREAMICE_calve_to_mask,
55 dgoldberg 1.10 ! & STREAMICE_geom_file_setup,
56 dgoldberg 1.6 & STREAMICE_diagnostic_only,
57 dgoldberg 1.2 ! & STREAMICE_construct_matrix,
58 heimbach 1.1 & STREAMICE_lower_cg_tol,
59 heimbach 1.4 & streamice_CFL_factor,
60 dgoldberg 1.6 & streamice_adjDump,
61     ! & STREAMICE_hybrid_stress,
62     & streamice_bg_surf_slope_x, streamice_bg_surf_slope_y,
63     & streamice_kx_b_init, streamice_ky_b_init,
64     & STREAMICEbasalTracConfig,
65     & STREAMICEbasalTracFile,
66 dgoldberg 1.7 & STREAMICEvelOptimFile,
67 dgoldberg 1.12 & STREAMICEtopogFile,
68 dgoldberg 1.10 & STREAMICEhmaskFile,
69     & STREAMICEuFaceBdryFile,
70     & STREAMICEvFaceBdryFile,
71     & STREAMICEuDirichValsFile,
72     & STREAMICEvDirichValsFile,
73     & STREAMICEGlenConstFile, STREAMICEGlenConstConfig,
74 dgoldberg 1.7 & STREAMICE_ppm_driving_stress,
75 dgoldberg 1.8 & STREAMICE_h_ctrl_const_surf,
76     & streamice_wgt_drift,streamice_wgt_surf,streamice_wgt_vel,
77 dgoldberg 1.10 & streamice_wgt_avthick, streamice_wgt_tikh,
78 dgoldberg 1.12 & streamice_addl_backstress,
79 dgoldberg 1.13 & streamice_smooth_gl_width,
80     & PETSC_PRECOND_TYPE, PETSC_SOLVER_TYPE
81 dgoldberg 1.6
82 heimbach 1.1
83     NAMELIST /STREAMICE_PARM02/
84     & shelf_max_draft,
85     & shelf_min_draft,
86     & shelf_edge_pos,
87     & shelf_slope_scale,
88     & shelf_flat_width,
89     & flow_dir
90    
91     NAMELIST /STREAMICE_PARM03/
92     & min_x_noflow_NORTH, max_x_noflow_NORTH,
93     & min_x_noflow_SOUTH, max_x_noflow_SOUTH,
94     & min_y_noflow_WEST, max_y_noflow_WEST,
95     & min_y_noflow_EAST, max_y_noflow_EAST,
96     & min_x_noStress_NORTH, max_x_noStress_NORTH,
97     & min_x_noStress_SOUTH, max_x_noStress_SOUTH,
98     & min_y_noStress_WEST, max_y_noStress_WEST,
99     & min_y_noStress_EAST, max_y_noStress_EAST,
100     & min_x_FluxBdry_NORTH, max_x_FluxBdry_NORTH,
101     & min_x_FluxBdry_SOUTH, max_x_FluxBdry_SOUTH,
102     & min_y_FluxBdry_WEST, max_y_FluxBdry_WEST,
103     & min_y_FluxBdry_EAST, max_y_FluxBdry_EAST,
104     & min_x_Dirich_NORTH, max_x_Dirich_NORTH,
105     & min_x_Dirich_SOUTH, max_x_Dirich_SOUTH,
106     & min_y_Dirich_WEST, max_y_Dirich_WEST,
107     & min_y_Dirich_EAST, max_y_Dirich_EAST,
108     & min_x_CFBC_NORTH, max_x_CFBC_NORTH,
109     & min_x_CFBC_SOUTH, max_x_CFBC_SOUTH,
110     & min_y_CFBC_WEST, max_y_CFBC_WEST,
111     & min_y_CFBC_EAST, max_y_CFBC_EAST,
112     & flux_bdry_val_SOUTH, flux_bdry_val_NORTH,
113 dgoldberg 1.6 & flux_bdry_val_WEST, flux_bdry_val_EAST,
114     & STREAMICE_NS_periodic, STREAMICE_EW_periodic
115 heimbach 1.1
116     _BEGIN_MASTER(myThid)
117    
118     C-- Default values for STREAMICE
119    
120     streamice_density = 917.
121     streamice_density_ocean_avg = 1024.
122 dgoldberg 1.12 B_glen_isothermal = 9.461e-18 ! Pa (-1/3) a
123 heimbach 1.1 n_glen = 3.
124     eps_glen_min = 1.0e-12
125 dgoldberg 1.9 eps_u_min = 1.0e-6
126 heimbach 1.1 C_basal_fric_const = 31.71 ! Pa (m/a)-1n
127     n_basal_friction = 1.
128     streamice_vel_update = 169200. ! seconds
129     streamice_cg_tol = 1e-6
130     streamice_nonlin_tol = 1e-6
131 dgoldberg 1.5 streamice_nonlin_tol_fp = 1.e-14
132 heimbach 1.1 streamice_max_cg_iter = 2000
133     streamice_max_nl_iter = 100
134     streamice_n_sub_regularize = 4
135     streamice_CFL_factor = .5
136 heimbach 1.4 streamice_adjDump = 0.
137 dgoldberg 1.6 streamice_bg_surf_slope_x = .0
138     streamice_bg_surf_slope_y = 0.
139     streamice_kx_b_init = 1.
140     streamice_ky_b_init = 1.
141 dgoldberg 1.8 streamice_wgt_drift = 0.
142 dgoldberg 1.10 streamice_wgt_tikh = 0.
143 dgoldberg 1.8 streamice_wgt_surf = 0.
144     streamice_wgt_vel = 0.
145 dgoldberg 1.9 streamice_wgt_avthick = 0.
146 dgoldberg 1.12 streamice_addl_backstress = 0.0
147     streamice_smooth_gl_width = 0.0
148 dgoldberg 1.6
149 heimbach 1.1 STREAMICEthickInit = 'FILE'
150     STREAMICEthickFile = ' '
151     STREAMICEcalveMaskFile = ' '
152 dgoldberg 1.6 STREAMICEsigcoordInit = 'UNIFORM'
153     STREAMICEsigcoordFile = ' '
154     STREAMICEbasalTracConfig = 'UNIFORM'
155     STREAMICEbasalTracFile = ' '
156     STREAMICEvelOptimFile = ''
157 dgoldberg 1.12 STREAMICEtopogFile = ''
158 dgoldberg 1.10 STREAMICEhmaskFile = ''
159     STREAMICEuFaceBdryFile = ''
160     STREAMICEvFaceBdryFile = ''
161     STREAMICEuDirichValsFile = ''
162     STREAMICEvDirichValsFile = ''
163     STREAMICEGlenConstFile = ''
164 dgoldberg 1.12 STREAMICEcostMaskFile = ''
165 dgoldberg 1.11 STREAMICEGlenConstConfig = 'UNIFORM'
166 dgoldberg 1.13 PETSC_PRECOND_TYPE = 'PCBJACOBI'
167     PETSC_SOLVER_TYPE = 'KSPCG'
168 heimbach 1.1
169     STREAMICEison = .TRUE.
170     STREAMICE_tave_mdsio = .TRUE.
171     STREAMICE_dump_mdsio = .TRUE.
172     STREAMICE_dump_mnc = .FALSE.
173     STREAMICE_tave_mnc = .FALSE.
174     STREAMICE_GL_regularize = .FALSE.
175     STREAMICE_move_front = .FALSE.
176     STREAMICE_calve_to_mask = .FALSE.
177 dgoldberg 1.10 ! STREAMICE_geom_file_setup = .FALSE.
178 dgoldberg 1.2 ! STREAMICE_construct_matrix = .TRUE.
179 heimbach 1.1 STREAMICE_lower_cg_tol = .FALSE.
180 dgoldberg 1.6 STREAMICE_diagnostic_only = .FALSE.
181 dgoldberg 1.7 STREAMICE_ppm_driving_stress = .FALSE.
182     STREAMICE_h_ctrl_const_surf = .FALSE.
183 dgoldberg 1.6 ! STREAMICE_hybrid_stress= .FALSE.
184 heimbach 1.1
185     min_x_noflow_NORTH = 0.
186     max_x_noflow_NORTH = 0.
187     min_x_noflow_SOUTH = 0.
188     max_x_noflow_SOUTH = 0.
189     min_y_noflow_WEST = 0.
190     max_y_noflow_WEST = 0.
191     min_y_noflow_EAST = 0.
192     max_y_noflow_EAST = 0.
193     min_x_noStress_NORTH = 0.
194     max_x_noStress_NORTH = 0.
195     min_x_noStress_SOUTH = 0.
196     max_x_noStress_SOUTH = 0.
197     min_y_noStress_WEST = 0.
198     max_y_noStress_WEST = 0.
199     min_y_noStress_EAST = 0.
200     max_y_noStress_EAST = 0.
201     min_x_FluxBdry_NORTH = 0.
202     max_x_FluxBdry_NORTH = 0.
203     min_x_FluxBdry_SOUTH = 0.
204     max_x_FluxBdry_SOUTH = 0.
205     min_y_FluxBdry_WEST = 0.
206     max_y_FluxBdry_WEST = 0.
207     min_y_FluxBdry_EAST = 0.
208     max_y_FluxBdry_EAST = 0.
209     min_x_Dirich_NORTH = 0.
210     max_x_Dirich_NORTH = 0.
211     min_x_Dirich_SOUTH = 0.
212     max_x_Dirich_SOUTH = 0.
213     min_y_Dirich_WEST = 0.
214     max_y_Dirich_WEST = 0.
215     min_y_Dirich_EAST = 0.
216     max_y_Dirich_EAST = 0.
217     min_y_CFBC_WEST = 0.
218     max_y_CFBC_WEST = 0.
219     min_y_CFBC_EAST = 0.
220     max_y_CFBC_EAST = 0.
221     flux_bdry_val_SOUTH = 0.
222     flux_bdry_val_NORTH = 0.
223     flux_bdry_val_WEST = 0.
224     flux_bdry_val_EAST = 0.
225    
226 dgoldberg 1.6 STREAMICE_NS_periodic = .FALSE.
227     STREAMICE_EW_periodic = .FALSE.
228 heimbach 1.1
229     WRITE(msgBuf,'(A)') 'STREAMICE_READPARMS: opening data.streamice'
230     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
231     & SQUEEZE_RIGHT , 1)
232     CALL OPEN_COPY_DATA_FILE(
233     I 'data.streamice', 'STREAMICE_READPARMS',
234     O iUnit,
235     I myThid )
236    
237     C Read parameters from open data file
238     READ(UNIT=iUnit,NML=STREAMICE_PARM01)
239     WRITE(msgBuf,'(A)')
240     & 'STREAMICE_READPARMS: read first param block'
241     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
242     & SQUEEZE_RIGHT , 1)
243    
244     IF (TRIM(STREAMICEthickInit) .eq. "PARAM") THEN
245 dgoldberg 1.3 READ(UNIT=iUnit,NML=STREAMICE_PARM02)
246 heimbach 1.1 WRITE(msgBuf,'(A)')
247     & 'STREAMICE_READPARMS: read second param block'
248     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
249     & SQUEEZE_RIGHT , 1)
250     ENDIF
251    
252 dgoldberg 1.3 READ(UNIT=iUnit,NML=STREAMICE_PARM03)
253 heimbach 1.1 WRITE(msgBuf,'(A)')
254     & 'STREAMICE_READPARMS: read third param block'
255     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
256     & SQUEEZE_RIGHT , 1)
257     C Close the open data file
258     CLOSE(iUnit)
259    
260     streamice_nstep_velocity = NINT (streamice_vel_update / deltaT)
261    
262     C- Set Output type flags :
263    
264     #ifdef ALLOW_MNC
265     IF (useMNC) THEN
266     IF ( .NOT.outputTypesInclusive
267     & .AND. STREAMICE_tave_mnc ) STREAMICE_tave_mdsio = .FALSE.
268     IF ( .NOT.outputTypesInclusive
269     & .AND. STREAMICE_dump_mnc ) STREAMICE_dump_mdsio = .FALSE.
270     ENDIF
271     #endif
272    
273     _END_MASTER(myThid)
274    
275     C-- Everyone else must wait for the parameters to be loaded
276     _BARRIER
277    
278     #endif /* ALLOW_STREAMICE */
279    
280     RETURN
281     END

  ViewVC Help
Powered by ViewVC 1.1.22