/[MITgcm]/MITgcm/pkg/gmredi/gmredi_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/gmredi/gmredi_readparms.F

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


Revision 1.11 - (hide annotations) (download)
Fri Jul 29 18:24:35 2005 UTC (18 years, 11 months ago) by edhill
Branch: MAIN
Changes since 1.10: +94 -22 lines
 o MNC-ify the gmredi package -- tested and works w/ and w/o mnc
   for ideal_2D_oce and lab_sea on linux_ia32_g77

1 edhill 1.11 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_readparms.F,v 1.10 2005/01/03 14:35:37 jmc Exp $
2 jmc 1.8 C $Name: $
3 heimbach 1.1
4     #include "GMREDI_OPTIONS.h"
5    
6     SUBROUTINE GMREDI_READPARMS( myThid )
7     C /==========================================================\
8     C | SUBROUTINE GMREDI_READPARMS |
9     C | o Routine to initialize GM/Redi variables and constants. |
10     C |==========================================================|
11     C | Initialize GM/Redi parameters, read in data.gmredi |
12     C \==========================================================/
13     IMPLICIT NONE
14    
15     C === Global variables ===
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "GRID.h"
20     #include "GMREDI.h"
21    
22     C === Routine arguments ===
23     INTEGER myThid
24    
25     #ifdef ALLOW_GMREDI
26    
27     C-- GM/Redi parameter
28 jmc 1.8 C GM_Small_Number :: epsilon used in computing the slope
29     C GM_slopeSqCutoff :: slope^2 cut-off value
30 heimbach 1.1 NAMELIST /GM_PARM01/
31 jmc 1.6 & GM_AdvForm, GM_AdvSeparate,
32 jmc 1.5 & GM_isopycK,
33     & GM_background_K,
34 heimbach 1.1 & GM_taper_scheme,
35     & GM_maxSlope,
36 jmc 1.5 & GM_Kmin_horiz,
37 jmc 1.8 & GM_Small_Number, GM_slopeSqCutoff,
38 heimbach 1.1 & GM_Visbeck_alpha,
39     & GM_Visbeck_length,
40     & GM_Visbeck_depth,
41     & GM_Visbeck_maxval_K,
42     & GM_Scrit,
43 edhill 1.11 & GM_Sd,
44     & GM_MNC
45 heimbach 1.1 c & GM_dumpFreq,
46     c & GM_taveFreq
47    
48     C === Local variables ===
49     C msgBuf - Informational/error meesage buffer
50     C iUnit - Work variable for IO unit number
51     CHARACTER*(MAX_LEN_MBUF) msgBuf
52     INTEGER iUnit
53    
54     C-- GMREDI_READPARMS has been called so we know that
55     C the package is active.
56 edhill 1.11 GMRediIsOn = .TRUE.
57 heimbach 1.1
58     _BEGIN_MASTER(myThid)
59    
60     C-- Default values GM/Redi
61 jmc 1.5 GM_AdvForm = .FALSE.
62 jmc 1.6 GM_AdvSeparate = .FALSE.
63 jmc 1.5 GM_isopycK = -999.
64 heimbach 1.1 GM_background_K = 0.
65     GM_maxslope = 1.0D-2
66 jmc 1.5 GM_Kmin_horiz = 0.
67 jmc 1.8 GM_Small_Number = 1. _d -12
68 edhill 1.11 GM_slopeSqCutoff = 1. _d +48
69 heimbach 1.1 GM_taper_scheme = ' '
70     GM_Scrit = 0.004
71     GM_Sd = 0.001
72 edhill 1.11 GM_MNC = useMNC
73    
74 heimbach 1.1 C-- Default values GM/Redi I/O control
75 edhill 1.11 c GM_dumpFreq = -1.
76     c GM_taveFreq = -1.
77 heimbach 1.1
78     C-- Default values Visbeck
79     GM_Visbeck_alpha = 0.
80     GM_Visbeck_length = 200.D3
81     GM_Visbeck_depth = 1000.D0
82     GM_Visbeck_maxval_K = 2500.D0
83    
84 edhill 1.11 WRITE(msgBuf,'(A)') ' GM_READPARMS: opening data.gmredi'
85     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
86     & SQUEEZE_RIGHT , 1)
87     CALL OPEN_COPY_DATA_FILE(
88     I 'data.gmredi', 'GM_READPARMS',
89     O iUnit,
90     I myThid )
91    
92     C Read parameters from open data file
93 heimbach 1.1 READ(UNIT=iUnit,NML=GM_PARM01)
94 jmc 1.9 WRITE(msgBuf,'(A)') ' GM_READPARMS: finished reading data.gmredi'
95     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
96     & SQUEEZE_RIGHT , 1)
97 edhill 1.11 C Close the open data file
98 jmc 1.9 CLOSE(iUnit)
99    
100 jmc 1.5 C Default value for GM_isopycK is equal to GM_background_K :
101     IF (GM_isopycK.EQ.-999.) GM_isopycK = GM_background_K
102    
103 heimbach 1.1 C Some constants
104     GM_rMaxSlope=0.
105     if (GM_maxSlope.ne.0.) GM_rMaxSlope=1. / GM_maxSlope
106    
107 jmc 1.5 IF (GM_AdvForm) THEN
108     GM_skewflx = 0.
109     GM_advect = 1.
110     GM_ExtraDiag = GM_Visbeck_alpha.NE.0. .OR. GM_isopycK.NE.0.
111     ELSE
112     GM_skewflx = 1.
113     GM_advect = 0.
114     GM_ExtraDiag = GM_isopycK.NE.GM_background_K
115     ENDIF
116    
117 edhill 1.11 C Make sure that we locally honor the global MNC on/off flag
118     GM_MNC = GM_MNC .AND. useMNC
119     #ifndef ALLOW_MNC
120     C Fix to avoid running without getting any output:
121     GM_MNC = .FALSE.
122     #endif
123     GM_MDSIO = (.NOT. GM_MNC) .OR. outputTypesInclusive
124    
125 heimbach 1.1 _END_MASTER(myThid)
126    
127     C-- Everyone else must wait for the parameters to be loaded
128     _BARRIER
129    
130 edhill 1.11 #ifdef ALLOW_MNC
131     IF (useMNC) THEN
132     CALL MNC_CW_ADD_VNAME('Kux','U_xy_Hn__C__t', 4,5,myThid)
133     CALL MNC_CW_ADD_VATTR_TEXT('Kux','units','m^2/s', myThid)
134     CALL MNC_CW_ADD_VATTR_TEXT('Kux','description',
135     & 'GM Tensor Kux is K_11 element, X direction at U point',
136     & myThid)
137     C CALL MNC_CW_ADD_VATTR_TEXT('Kux',
138     C & 'coordinates','XC YC RC iter', myThid)
139    
140     CALL MNC_CW_ADD_VNAME('Kvy','V_xy_Hn__C__t', 4,5,myThid)
141     CALL MNC_CW_ADD_VATTR_TEXT('Kvy','units','m^2/s', myThid)
142     CALL MNC_CW_ADD_VATTR_TEXT('Kvy','description',
143     & 'GM Tensor Kvy is K_22 element, Y direction at V point',
144     & myThid)
145    
146     CALL MNC_CW_ADD_VNAME('Kuz','U_xy_Hn__C__t', 4,5,myThid)
147     CALL MNC_CW_ADD_VATTR_TEXT('Kuz','units','m^2/s', myThid)
148     CALL MNC_CW_ADD_VATTR_TEXT('Kuz','description',
149     & 'GM Tensor Kuz is K_13 element, Z direction at U point',
150     & myThid)
151    
152     CALL MNC_CW_ADD_VNAME('Kvz','V_xy_Hn__C__t', 4,5,myThid)
153     CALL MNC_CW_ADD_VATTR_TEXT('Kvz','units','m^2/s', myThid)
154     CALL MNC_CW_ADD_VATTR_TEXT('Kvz','description',
155     & 'GM Tensor Kvz is K_23 element, Z direction at V point',
156     & myThid)
157    
158     CALL MNC_CW_ADD_VNAME('Kwx','Cen_xy_Hn__L__t', 4,5,myThid)
159     CALL MNC_CW_ADD_VATTR_TEXT('Kwx','units','m^2/s', myThid)
160     CALL MNC_CW_ADD_VATTR_TEXT('Kwx','description',
161     & 'GM Tensor Kwx is K_31 element, X direction at W point',
162     & myThid)
163    
164     CALL MNC_CW_ADD_VNAME('Kwy','Cen_xy_Hn__L__t', 4,5,myThid)
165     CALL MNC_CW_ADD_VATTR_TEXT('Kwy','units','m^2/s', myThid)
166     CALL MNC_CW_ADD_VATTR_TEXT('Kwy','description',
167     & 'GM Tensor Kwy is K_32 element, Y direction at W point',
168     & myThid)
169    
170     CALL MNC_CW_ADD_VNAME('Kwz','Cen_xy_Hn__L__t', 4,5,myThid)
171     CALL MNC_CW_ADD_VATTR_TEXT('Kwz','units','m^2/s', myThid)
172     CALL MNC_CW_ADD_VATTR_TEXT('Kwz','description',
173     & 'GM Tensor Kwz is K_33 element, Z direction at W point',
174     & myThid)
175    
176     CALL MNC_CW_ADD_VNAME('VisbK','Cen_xy_Hn__C__t',4,5,myThid)
177     CALL MNC_CW_ADD_VATTR_TEXT('VisbK','units','m^2/s', myThid)
178     CALL MNC_CW_ADD_VATTR_TEXT('VisbK','description',
179     & 'GM mixing/stirring coef after Visbeck et al.',
180     & myThid)
181    
182     CALL MNC_CW_ADD_VNAME('PsiX','Cen_xy_Hn__C__t',4,5,myThid)
183     CALL MNC_CW_ADD_VATTR_TEXT('PsiX','units','m^2/s', myThid)
184     CALL MNC_CW_ADD_VATTR_TEXT('PsiX','description',
185     & 'GM bolus velocity streamfunction in X',
186     & myThid)
187    
188     CALL MNC_CW_ADD_VNAME('PsiY','Cen_xy_Hn__C__t',4,5,myThid)
189     CALL MNC_CW_ADD_VATTR_TEXT('PsiY','units','m^2/s', myThid)
190     CALL MNC_CW_ADD_VATTR_TEXT('PsiY','description',
191     & 'GM bolus velocity streamfunction in Y',
192     & myThid)
193    
194     ENDIF
195     #endif /* ALLOW_MNC */
196    
197 heimbach 1.1 #endif /* ALLOW_GMREDI */
198    
199 jmc 1.5 RETURN
200     END

  ViewVC Help
Powered by ViewVC 1.1.22