/[MITgcm]/MITgcm/pkg/obcs/obcs_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/obcs/obcs_readparms.F

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


Revision 1.19 - (show annotations) (download)
Wed Apr 23 16:34:05 2008 UTC (16 years, 1 month ago) by dimitri
Branch: MAIN
Changes since 1.18: +17 -11 lines
enclosed WRITE statements in obcs_readparms.F with
 IF ( debugLevel .GE. debLevB ) ... ENDIF

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.18 2008/01/24 18:39:38 mlosch Exp $
2 C $Name: $
3
4 #include "OBCS_OPTIONS.h"
5
6 SUBROUTINE OBCS_READPARMS( myThid )
7 C /==========================================================\
8 C | SUBROUTINE OBCS_READPARMS |
9 C | o Routine to initialize OBCS variables and constants. |
10 C |==========================================================|
11 C \==========================================================/
12 IMPLICIT NONE
13
14 C === Global variables ===
15 #include "SIZE.h"
16 #include "EEPARAMS.h"
17 #include "PARAMS.h"
18 #include "OBCS.h"
19 #ifdef ALLOW_ORLANSKI
20 #include "ORLANSKI.h"
21 #endif
22 #ifdef ALLOW_PTRACERS
23 #include "PTRACERS_SIZE.h"
24 #include "OBCS_PTRACERS.h"
25 #endif /* ALLOW_PTRACERS */
26
27 C === Routine arguments ===
28 INTEGER myThid
29
30 #ifdef ALLOW_OBCS
31
32 C === Local variables ===
33 C msgBuf - Informational/error meesage buffer
34 C iUnit - Work variable for IO unit number
35 CHARACTER*(MAX_LEN_MBUF) msgBuf
36 INTEGER iUnit
37 INTEGER I,J,iTracer
38
39 NAMELIST /OBCS_PARM01/
40 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
41 & useOrlanskiNorth,useOrlanskiSouth,
42 & useOrlanskiEast,useOrlanskiWest,
43 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,OBNaFile,OBNhFile,
44 & OBSuFile,OBSvFile,OBStFile,OBSsFile,OBSaFile,OBShFile,
45 & OBEuFile,OBEvFile,OBEtFile,OBEsFile,OBEaFile,OBEhFile,
46 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,OBWaFile,OBWhFile,
47 & OBNslFile,OBSslFile,OBEslFile,OBWslFile,
48 & OBNsnFile,OBSsnFile,OBEsnFile,OBWsnFile,
49 & OBNuiceFile,OBSuiceFile,OBEuiceFile,OBWuiceFile,
50 & OBNviceFile,OBSviceFile,OBEviceFile,OBWviceFile,
51 & useOBCSsponge, useOBCSbalance, useOBCSprescribe,
52 & OBCSprintDiags, useOBCSYearlyFields
53 #ifdef ALLOW_PTRACERS
54 & , OBNptrFile,OBSptrFile,OBEptrFile,OBWptrFile
55 #endif
56
57 #ifdef ALLOW_ORLANSKI
58 NAMELIST /OBCS_PARM02/
59 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
60 #endif
61
62 #ifdef ALLOW_OBCS_SPONGE
63 NAMELIST /OBCS_PARM03/
64 & Urelaxobcsinner,Urelaxobcsbound,
65 & Vrelaxobcsinner,Vrelaxobcsbound,
66 & spongeThickness
67 #endif
68
69 _BEGIN_MASTER(myThid)
70
71 C-- OBCS_READPARMS has been called so we know that
72 C the package is active.
73 OBCSIsOn=.TRUE.
74
75 IF ( debugLevel .GE. debLevB ) THEN
76 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
77 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
78 & SQUEEZE_RIGHT , 1)
79 ENDIF
80
81 CALL OPEN_COPY_DATA_FILE(
82 I 'data.obcs', 'OBCS_READPARMS',
83 O iUnit,
84 I myThid )
85
86 C-- Default flags and values for OBCS
87 DO I=1,Nx
88 OB_Jnorth(I)=0
89 OB_Jsouth(I)=0
90 ENDDO
91 DO J=1,Ny
92 OB_Ieast(J)=0
93 OB_Iwest(J)=0
94 ENDDO
95 useOrlanskiNorth =.FALSE.
96 useOrlanskiSouth =.FALSE.
97 useOrlanskiEast =.FALSE.
98 useOrlanskiWest =.FALSE.
99 useOBCSsponge =.FALSE.
100 useOBCSbalance =.FALSE.
101 useOBCSprescribe =.FALSE.
102 OBCSprintDiags =.TRUE.
103 useOBCSYearlyFields=.FALSE.
104
105 OBNuFile = ' '
106 OBNvFile = ' '
107 OBNtFile = ' '
108 OBNsFile = ' '
109 OBNaFile = ' '
110 OBNslFile = ' '
111 OBNsnFile = ' '
112 OBNuiceFile = ' '
113 OBNviceFile = ' '
114 OBNhFile = ' '
115 OBSuFile = ' '
116 OBSvFile = ' '
117 OBStFile = ' '
118 OBSsFile = ' '
119 OBSaFile = ' '
120 OBShFile = ' '
121 OBSslFile = ' '
122 OBSsnFile = ' '
123 OBSuiceFile = ' '
124 OBSviceFile = ' '
125 OBEuFile = ' '
126 OBEvFile = ' '
127 OBEtFile = ' '
128 OBEsFile = ' '
129 OBEaFile = ' '
130 OBEhFile = ' '
131 OBEslFile = ' '
132 OBEsnFile = ' '
133 OBEuiceFile = ' '
134 OBEviceFile = ' '
135 OBWuFile = ' '
136 OBWvFile = ' '
137 OBWtFile = ' '
138 OBWsFile = ' '
139 OBWaFile = ' '
140 OBWhFile = ' '
141 OBWslFile = ' '
142 OBWsnFile = ' '
143 OBWuiceFile = ' '
144 OBWviceFile = ' '
145 #ifdef ALLOW_PTRACERS
146 DO iTracer = 1, PTRACERS_num
147 OBNptrFile(iTracer) = ' '
148 OBSptrFile(iTracer) = ' '
149 OBEptrFile(iTracer) = ' '
150 OBWptrFile(iTracer) = ' '
151 ENDDO
152 #endif
153
154 C-- Read parameters from open data file
155 READ(UNIT=iUnit,NML=OBCS_PARM01)
156
157 C Account for periodicity if negative indices were supplied
158 DO J=1,Ny
159 IF (OB_Ieast(J).lt.0) OB_Ieast(J)=OB_Ieast(J)+Nx+1
160 ENDDO
161 DO I=1,Nx
162 IF (OB_Jnorth(I).lt.0) OB_Jnorth(I)=OB_Jnorth(I)+Ny+1
163 ENDDO
164 IF ( debugLevel .GE. debLevB ) THEN
165 write(*,*) 'OB Jn =',OB_Jnorth
166 write(*,*) 'OB Js =',OB_Jsouth
167 write(*,*) 'OB Ie =',OB_Ieast
168 write(*,*) 'OB Iw =',OB_Iwest
169 ENDIF
170
171 #ifdef ALLOW_ORLANSKI
172 C Default Orlanski radiation parameters
173 CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
174 cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed in sec. */
175 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
176 useFixedCEast=.FALSE.
177 useFixedCWest=.FALSE.
178 IF (useOrlanskiNorth.OR.
179 & useOrlanskiSouth.OR.
180 & useOrlanskiEast.OR.
181 & useOrlanskiWest)
182 & READ(UNIT=iUnit,NML=OBCS_PARM02)
183 #endif
184
185 #ifdef ALLOW_OBCS_SPONGE
186 C Default sponge layer parameters:
187 C sponge layer is turned off by default
188 spongeThickness = 0
189 Urelaxobcsinner = 0. _d 0
190 Urelaxobcsbound = 0. _d 0
191 Vrelaxobcsinner = 0. _d 0
192 Vrelaxobcsbound = 0. _d 0
193 CML this was the previous default in units of days
194 CML spongeThickness = 2
195 CML Urelaxobcsinner = 5. _d 0
196 CML Urelaxobcsbound = 1. _d 0
197 CML Vrelaxobcsinner = 5. _d 0
198 CML Vrelaxobcsbound = 1. _d 0
199 IF (useOBCSsponge)
200 & READ(UNIT=iUnit,NML=OBCS_PARM03)
201 #endif
202
203 IF ( debugLevel .GE. debLevB ) THEN
204 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
205 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
206 & SQUEEZE_RIGHT , 1)
207 ENDIF
208
209 C-- Close the open data file
210 CLOSE(iUnit)
211 _END_MASTER(myThid)
212
213 C-- Everyone else must wait for the parameters to be loaded
214 _BARRIER
215
216 #endif /* ALLOW_OBCS */
217 RETURN
218 END

  ViewVC Help
Powered by ViewVC 1.1.22