/[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.4 - (hide annotations) (download)
Fri Jul 27 21:07:13 2012 UTC (12 years, 11 months ago) by heimbach
Branch: MAIN
Changes since 1.3: +4 -2 lines
Enable transient I/O

1 heimbach 1.4 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_readparms.F,v 1.3 2012/07/24 20:49:41 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     & A_glen_isothermal, n_glen, eps_glen_min,
39     & C_basal_fric_const, n_basal_friction,
40     & streamice_vel_update,streamice_cg_tol,streamice_nonlin_tol,
41     & streamice_max_cg_iter, streamice_max_nl_iter,
42     & STREAMICE_GL_regularize,
43     & STREAMICEthickInit,
44     & STREAMICEthickFile,
45     & STREAMICEcalveMaskFile,
46     & STREAMICEison,
47     & STREAMICE_dump_mdsio, STREAMICE_tave_mdsio,
48     & STREAMICE_dump_mnc, STREAMICE_tave_mnc,
49     & STREAMICE_GL_regularize, STREAMICE_move_front,
50     & STREAMICE_calve_to_mask,
51 dgoldberg 1.2 ! & STREAMICE_construct_matrix,
52 heimbach 1.1 & STREAMICE_lower_cg_tol,
53 heimbach 1.4 & streamice_CFL_factor,
54     & streamice_adjDump
55 heimbach 1.1
56     NAMELIST /STREAMICE_PARM02/
57     & shelf_max_draft,
58     & shelf_min_draft,
59     & shelf_edge_pos,
60     & shelf_slope_scale,
61     & shelf_flat_width,
62     & flow_dir
63    
64     NAMELIST /STREAMICE_PARM03/
65     & min_x_noflow_NORTH, max_x_noflow_NORTH,
66     & min_x_noflow_SOUTH, max_x_noflow_SOUTH,
67     & min_y_noflow_WEST, max_y_noflow_WEST,
68     & min_y_noflow_EAST, max_y_noflow_EAST,
69     & min_x_noStress_NORTH, max_x_noStress_NORTH,
70     & min_x_noStress_SOUTH, max_x_noStress_SOUTH,
71     & min_y_noStress_WEST, max_y_noStress_WEST,
72     & min_y_noStress_EAST, max_y_noStress_EAST,
73     & min_x_FluxBdry_NORTH, max_x_FluxBdry_NORTH,
74     & min_x_FluxBdry_SOUTH, max_x_FluxBdry_SOUTH,
75     & min_y_FluxBdry_WEST, max_y_FluxBdry_WEST,
76     & min_y_FluxBdry_EAST, max_y_FluxBdry_EAST,
77     & min_x_Dirich_NORTH, max_x_Dirich_NORTH,
78     & min_x_Dirich_SOUTH, max_x_Dirich_SOUTH,
79     & min_y_Dirich_WEST, max_y_Dirich_WEST,
80     & min_y_Dirich_EAST, max_y_Dirich_EAST,
81     & min_x_CFBC_NORTH, max_x_CFBC_NORTH,
82     & min_x_CFBC_SOUTH, max_x_CFBC_SOUTH,
83     & min_y_CFBC_WEST, max_y_CFBC_WEST,
84     & min_y_CFBC_EAST, max_y_CFBC_EAST,
85     & flux_bdry_val_SOUTH, flux_bdry_val_NORTH,
86     & flux_bdry_val_WEST, flux_bdry_val_EAST
87    
88     _BEGIN_MASTER(myThid)
89    
90     C-- Default values for STREAMICE
91    
92     streamice_density = 917.
93     streamice_density_ocean_avg = 1024.
94     A_glen_isothermal = 9.461e-18 ! Pa (-1/3) a
95     n_glen = 3.
96     eps_glen_min = 1.0e-12
97     C_basal_fric_const = 31.71 ! Pa (m/a)-1n
98     n_basal_friction = 1.
99     streamice_vel_update = 169200. ! seconds
100     streamice_cg_tol = 1e-6
101     streamice_nonlin_tol = 1e-6
102     streamice_max_cg_iter = 2000
103     streamice_max_nl_iter = 100
104     streamice_n_sub_regularize = 4
105     streamice_CFL_factor = .5
106 heimbach 1.4 streamice_adjDump = 0.
107 heimbach 1.1
108     STREAMICEthickInit = 'FILE'
109     STREAMICEthickFile = ' '
110     STREAMICEcalveMaskFile = ' '
111    
112     STREAMICEison = .TRUE.
113     STREAMICE_tave_mdsio = .TRUE.
114     STREAMICE_dump_mdsio = .TRUE.
115     STREAMICE_dump_mnc = .FALSE.
116     STREAMICE_tave_mnc = .FALSE.
117     STREAMICE_GL_regularize = .FALSE.
118     STREAMICE_move_front = .FALSE.
119     STREAMICE_calve_to_mask = .FALSE.
120 dgoldberg 1.2 ! STREAMICE_construct_matrix = .TRUE.
121 heimbach 1.1 STREAMICE_lower_cg_tol = .FALSE.
122    
123     min_x_noflow_NORTH = 0.
124     max_x_noflow_NORTH = 0.
125     min_x_noflow_SOUTH = 0.
126     max_x_noflow_SOUTH = 0.
127     min_y_noflow_WEST = 0.
128     max_y_noflow_WEST = 0.
129     min_y_noflow_EAST = 0.
130     max_y_noflow_EAST = 0.
131     min_x_noStress_NORTH = 0.
132     max_x_noStress_NORTH = 0.
133     min_x_noStress_SOUTH = 0.
134     max_x_noStress_SOUTH = 0.
135     min_y_noStress_WEST = 0.
136     max_y_noStress_WEST = 0.
137     min_y_noStress_EAST = 0.
138     max_y_noStress_EAST = 0.
139     min_x_FluxBdry_NORTH = 0.
140     max_x_FluxBdry_NORTH = 0.
141     min_x_FluxBdry_SOUTH = 0.
142     max_x_FluxBdry_SOUTH = 0.
143     min_y_FluxBdry_WEST = 0.
144     max_y_FluxBdry_WEST = 0.
145     min_y_FluxBdry_EAST = 0.
146     max_y_FluxBdry_EAST = 0.
147     min_x_Dirich_NORTH = 0.
148     max_x_Dirich_NORTH = 0.
149     min_x_Dirich_SOUTH = 0.
150     max_x_Dirich_SOUTH = 0.
151     min_y_Dirich_WEST = 0.
152     max_y_Dirich_WEST = 0.
153     min_y_Dirich_EAST = 0.
154     max_y_Dirich_EAST = 0.
155     min_y_CFBC_WEST = 0.
156     max_y_CFBC_WEST = 0.
157     min_y_CFBC_EAST = 0.
158     max_y_CFBC_EAST = 0.
159     flux_bdry_val_SOUTH = 0.
160     flux_bdry_val_NORTH = 0.
161     flux_bdry_val_WEST = 0.
162     flux_bdry_val_EAST = 0.
163    
164    
165     WRITE(msgBuf,'(A)') 'STREAMICE_READPARMS: opening data.streamice'
166     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
167     & SQUEEZE_RIGHT , 1)
168     CALL OPEN_COPY_DATA_FILE(
169     I 'data.streamice', 'STREAMICE_READPARMS',
170     O iUnit,
171     I myThid )
172    
173     C Read parameters from open data file
174     READ(UNIT=iUnit,NML=STREAMICE_PARM01)
175     WRITE(msgBuf,'(A)')
176     & 'STREAMICE_READPARMS: read first param block'
177     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
178     & SQUEEZE_RIGHT , 1)
179    
180     IF (TRIM(STREAMICEthickInit) .eq. "PARAM") THEN
181 dgoldberg 1.3 READ(UNIT=iUnit,NML=STREAMICE_PARM02)
182 heimbach 1.1 WRITE(msgBuf,'(A)')
183     & 'STREAMICE_READPARMS: read second param block'
184     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
185     & SQUEEZE_RIGHT , 1)
186     ENDIF
187    
188 dgoldberg 1.3 READ(UNIT=iUnit,NML=STREAMICE_PARM03)
189 heimbach 1.1 WRITE(msgBuf,'(A)')
190     & 'STREAMICE_READPARMS: read third param block'
191     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
192     & SQUEEZE_RIGHT , 1)
193     C Close the open data file
194     CLOSE(iUnit)
195    
196     streamice_nstep_velocity = NINT (streamice_vel_update / deltaT)
197    
198     C- Set Output type flags :
199    
200     #ifdef ALLOW_MNC
201     IF (useMNC) THEN
202     IF ( .NOT.outputTypesInclusive
203     & .AND. STREAMICE_tave_mnc ) STREAMICE_tave_mdsio = .FALSE.
204     IF ( .NOT.outputTypesInclusive
205     & .AND. STREAMICE_dump_mnc ) STREAMICE_dump_mdsio = .FALSE.
206     ENDIF
207     #endif
208    
209     _END_MASTER(myThid)
210    
211     C-- Everyone else must wait for the parameters to be loaded
212     _BARRIER
213    
214     #endif /* ALLOW_STREAMICE */
215    
216     RETURN
217     END

  ViewVC Help
Powered by ViewVC 1.1.22