/[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.20 - (hide annotations) (download)
Thu Apr 24 07:42:37 2008 UTC (17 years, 3 months ago) by mlosch
Branch: MAIN
Changes since 1.19: +51 -1 lines
move computation of index fields OB_Jn/Js/Ie/Iw from obcs_init_fixed to
obcs_readpams in preparation for code that fixes topography gradients
normal to open boundaries

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

  ViewVC Help
Powered by ViewVC 1.1.22