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

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

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


Revision 1.24 - (hide annotations) (download)
Mon Oct 5 18:49:29 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.23: +3 -3 lines
default value for OBCSprintDiags set to debugLevel.GE.debLevB

1 jmc 1.24 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.23 2009/08/11 15:46:27 mlosch Exp $
2 heimbach 1.7 C $Name: $
3 adcroft 1.2
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 jmc 1.17 #ifdef ALLOW_PTRACERS
23 mlosch 1.11 #include "PTRACERS_SIZE.h"
24     #include "OBCS_PTRACERS.h"
25     #endif /* ALLOW_PTRACERS */
26 adcroft 1.2
27     C === Routine arguments ===
28     INTEGER myThid
29    
30     #ifdef ALLOW_OBCS
31    
32 jmc 1.13 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 mlosch 1.20 INTEGER bi, bj, iG, jG, iGm, jGm
39 jmc 1.13
40 adcroft 1.2 NAMELIST /OBCS_PARM01/
41     & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
42     & useOrlanskiNorth,useOrlanskiSouth,
43 heimbach 1.5 & useOrlanskiEast,useOrlanskiWest,
44 dimitri 1.14 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,OBNaFile,OBNhFile,
45     & OBSuFile,OBSvFile,OBStFile,OBSsFile,OBSaFile,OBShFile,
46     & OBEuFile,OBEvFile,OBEtFile,OBEsFile,OBEaFile,OBEhFile,
47     & OBWuFile,OBWvFile,OBWtFile,OBWsFile,OBWaFile,OBWhFile,
48 dimitri 1.15 & OBNslFile,OBSslFile,OBEslFile,OBWslFile,
49     & OBNsnFile,OBSsnFile,OBEsnFile,OBWsnFile,
50 dimitri 1.16 & OBNuiceFile,OBSuiceFile,OBEuiceFile,OBWuiceFile,
51     & OBNviceFile,OBSviceFile,OBEviceFile,OBWviceFile,
52 mlosch 1.12 & useOBCSsponge, useOBCSbalance, useOBCSprescribe,
53 mlosch 1.21 & OBCSprintDiags, useOBCSYearlyFields, OBCSfixTopo
54 mlosch 1.23 #ifdef NONLIN_FRSURF
55     & , OBNetaFile, OBSetaFile, OBEetaFile, OBWetaFile
56     #endif /* NONLIN_FRSURF */
57 mlosch 1.11 #ifdef ALLOW_PTRACERS
58     & , OBNptrFile,OBSptrFile,OBEptrFile,OBWptrFile
59     #endif
60 adcroft 1.3
61     #ifdef ALLOW_ORLANSKI
62     NAMELIST /OBCS_PARM02/
63 adcroft 1.6 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
64 adcroft 1.3 #endif
65 adcroft 1.2
66 heimbach 1.7 #ifdef ALLOW_OBCS_SPONGE
67     NAMELIST /OBCS_PARM03/
68     & Urelaxobcsinner,Urelaxobcsbound,
69     & Vrelaxobcsinner,Vrelaxobcsbound,
70     & spongeThickness
71     #endif
72    
73 jmc 1.13 _BEGIN_MASTER(myThid)
74 adcroft 1.2
75     C-- OBCS_READPARMS has been called so we know that
76     C the package is active.
77     OBCSIsOn=.TRUE.
78    
79 dimitri 1.19 IF ( debugLevel .GE. debLevB ) THEN
80     WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
81     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
82     & SQUEEZE_RIGHT , 1)
83     ENDIF
84 adcroft 1.2
85     CALL OPEN_COPY_DATA_FILE(
86     I 'data.obcs', 'OBCS_READPARMS',
87     O iUnit,
88     I myThid )
89    
90     C-- Default flags and values for OBCS
91     DO I=1,Nx
92     OB_Jnorth(I)=0
93     OB_Jsouth(I)=0
94     ENDDO
95     DO J=1,Ny
96     OB_Ieast(J)=0
97     OB_Iwest(J)=0
98     ENDDO
99 mlosch 1.18 useOrlanskiNorth =.FALSE.
100     useOrlanskiSouth =.FALSE.
101     useOrlanskiEast =.FALSE.
102     useOrlanskiWest =.FALSE.
103     useOBCSsponge =.FALSE.
104     useOBCSbalance =.FALSE.
105     useOBCSprescribe =.FALSE.
106 jmc 1.24 OBCSprintDiags = debugLevel.GE.debLevB
107 mlosch 1.18 useOBCSYearlyFields=.FALSE.
108 mlosch 1.22 OBCSfixTopo =.TRUE.
109 heimbach 1.5
110     OBNuFile = ' '
111     OBNvFile = ' '
112     OBNtFile = ' '
113     OBNsFile = ' '
114 dimitri 1.14 OBNaFile = ' '
115 dimitri 1.15 OBNslFile = ' '
116     OBNsnFile = ' '
117 dimitri 1.16 OBNuiceFile = ' '
118     OBNviceFile = ' '
119 dimitri 1.14 OBNhFile = ' '
120 heimbach 1.5 OBSuFile = ' '
121     OBSvFile = ' '
122     OBStFile = ' '
123     OBSsFile = ' '
124 dimitri 1.14 OBSaFile = ' '
125     OBShFile = ' '
126 dimitri 1.15 OBSslFile = ' '
127     OBSsnFile = ' '
128 dimitri 1.16 OBSuiceFile = ' '
129     OBSviceFile = ' '
130 heimbach 1.5 OBEuFile = ' '
131     OBEvFile = ' '
132     OBEtFile = ' '
133     OBEsFile = ' '
134 dimitri 1.14 OBEaFile = ' '
135     OBEhFile = ' '
136 dimitri 1.15 OBEslFile = ' '
137     OBEsnFile = ' '
138 dimitri 1.16 OBEuiceFile = ' '
139     OBEviceFile = ' '
140 heimbach 1.5 OBWuFile = ' '
141     OBWvFile = ' '
142     OBWtFile = ' '
143     OBWsFile = ' '
144 dimitri 1.14 OBWaFile = ' '
145     OBWhFile = ' '
146 dimitri 1.15 OBWslFile = ' '
147     OBWsnFile = ' '
148 dimitri 1.16 OBWuiceFile = ' '
149     OBWviceFile = ' '
150 mlosch 1.23 OBNetaFile = ' '
151     OBSetaFile = ' '
152     OBEetaFile = ' '
153     OBWetaFile = ' '
154 mlosch 1.11 #ifdef ALLOW_PTRACERS
155     DO iTracer = 1, PTRACERS_num
156     OBNptrFile(iTracer) = ' '
157     OBSptrFile(iTracer) = ' '
158     OBEptrFile(iTracer) = ' '
159     OBWptrFile(iTracer) = ' '
160     ENDDO
161     #endif
162 adcroft 1.2
163     C-- Read parameters from open data file
164     READ(UNIT=iUnit,NML=OBCS_PARM01)
165    
166     C Account for periodicity if negative indices were supplied
167     DO J=1,Ny
168     IF (OB_Ieast(J).lt.0) OB_Ieast(J)=OB_Ieast(J)+Nx+1
169     ENDDO
170     DO I=1,Nx
171     IF (OB_Jnorth(I).lt.0) OB_Jnorth(I)=OB_Jnorth(I)+Ny+1
172     ENDDO
173 dimitri 1.19 IF ( debugLevel .GE. debLevB ) THEN
174     write(*,*) 'OB Jn =',OB_Jnorth
175     write(*,*) 'OB Js =',OB_Jsouth
176     write(*,*) 'OB Ie =',OB_Ieast
177     write(*,*) 'OB Iw =',OB_Iwest
178     ENDIF
179 adcroft 1.2
180 adcroft 1.3 #ifdef ALLOW_ORLANSKI
181     C Default Orlanski radiation parameters
182     CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
183     cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed in sec. */
184 adcroft 1.6 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
185     useFixedCEast=.FALSE.
186     useFixedCWest=.FALSE.
187 adcroft 1.3 IF (useOrlanskiNorth.OR.
188     & useOrlanskiSouth.OR.
189     & useOrlanskiEast.OR.
190 jmc 1.13 & useOrlanskiWest)
191 adcroft 1.3 & READ(UNIT=iUnit,NML=OBCS_PARM02)
192 adcroft 1.2 #endif
193 jmc 1.13
194 heimbach 1.7 #ifdef ALLOW_OBCS_SPONGE
195 mlosch 1.10 C Default sponge layer parameters:
196     C sponge layer is turned off by default
197     spongeThickness = 0
198     Urelaxobcsinner = 0. _d 0
199     Urelaxobcsbound = 0. _d 0
200     Vrelaxobcsinner = 0. _d 0
201     Vrelaxobcsbound = 0. _d 0
202     CML this was the previous default in units of days
203     CML spongeThickness = 2
204     CML Urelaxobcsinner = 5. _d 0
205     CML Urelaxobcsbound = 1. _d 0
206     CML Vrelaxobcsinner = 5. _d 0
207     CML Vrelaxobcsbound = 1. _d 0
208 heimbach 1.7 IF (useOBCSsponge)
209     & READ(UNIT=iUnit,NML=OBCS_PARM03)
210     #endif
211    
212 dimitri 1.19 IF ( debugLevel .GE. debLevB ) THEN
213     WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
214     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
215     & SQUEEZE_RIGHT , 1)
216     ENDIF
217 adcroft 1.2
218     C-- Close the open data file
219     CLOSE(iUnit)
220     _END_MASTER(myThid)
221    
222     C-- Everyone else must wait for the parameters to be loaded
223     _BARRIER
224    
225 jmc 1.24 C-- Calculate the tiled index arrays OB_Jn/Js/Ie/Iw here from the
226 mlosch 1.20 C global arrays OB_Jnorth/Jsouth/Ieast/Iwest.
227     C Note: This part of the code has been moved from obcs_init_fixed to
228     C routine routine because the OB_Jn/Js/Ie/Iw index arrays are
229     C required by ini_depth which is called befoer obcs_init_fixed
230     DO bj = myByLo(myThid), myByHi(myThid)
231     DO bi = myBxLo(myThid), myBxHi(myThid)
232    
233     DO I=1-Olx,sNx+Olx
234     OB_Jn(I,bi,bj)=0
235     OB_Js(I,bi,bj)=0
236     ENDDO
237    
238     DO J=1-Oly,sNy+Oly
239     OB_Ie(J,bi,bj)=0
240     OB_Iw(J,bi,bj)=0
241     ENDDO
242    
243     DO J=1-Oly,sNy+Oly
244     C convert from local y index J to global y index jG
245     jG = myYGlobalLo-1+(bj-1)*sNy+J
246     C use periodicity to deal with out of range points caused by the overlaps.
247     C they will be excluded by the mask in any case, but this saves array
248     C out-of-bounds errors here.
249     jGm = 1+mod( jG-1+Ny , Ny )
250     C loop over local x index I
251     DO I=1,sNx
252     iG = myXGlobalLo-1+(bi-1)*sNx+I
253     iGm = 1+mod( iG-1+Nx , Nx )
254     C OB_Ieast(jGm) allows for the eastern boundary to be at variable x locations
255     IF (iG.EQ.OB_Ieast(jGm)) OB_Ie(J,bi,bj)=I
256     IF (iG.EQ.OB_Iwest(jGm)) OB_Iw(J,bi,bj)=I
257     ENDDO
258     ENDDO
259     DO J=1,sNy
260     jG = myYGlobalLo-1+(bj-1)*sNy+J
261     jGm = 1+mod( jG-1+Ny , Ny )
262     DO I=1-Olx,sNx+Olx
263     iG = myXGlobalLo-1+(bi-1)*sNx+I
264     iGm = 1+mod( iG-1+Nx , Nx )
265     C OB_Jnorth(iGm) allows for the northern boundary to be at variable y locations
266     IF (jG.EQ.OB_Jnorth(iGm)) OB_Jn(I,bi,bj)=J
267     IF (jG.EQ.OB_Jsouth(iGm)) OB_Js(I,bi,bj)=J
268     ENDDO
269     ENDDO
270     C bi,bj-loops
271     ENDDO
272     ENDDO
273    
274 adcroft 1.2 #endif /* ALLOW_OBCS */
275     RETURN
276     END

  ViewVC Help
Powered by ViewVC 1.1.22