/[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.22 - (hide annotations) (download)
Fri Apr 25 12:13:38 2008 UTC (17 years, 2 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59r, checkpoint61f, checkpoint61n, checkpoint61q, checkpoint61e, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61r, checkpoint61s, checkpoint61p
Changes since 1.21: +2 -2 lines
o pkg/obcs: change default to OBCSfixTopo = .true.,

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

  ViewVC Help
Powered by ViewVC 1.1.22