/[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.13 - (hide annotations) (download)
Tue Oct 17 19:00:44 2006 UTC (17 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_post, checkpoint58w_post, checkpoint58q_post, checkpoint58r_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint58v_post, checkpoint58x_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.12: +11 -11 lines
clean-up multi-threaded problems (reported by debugger tcheck on ACES)

1 jmc 1.13 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.12 2006/04/04 07:46:17 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 mlosch 1.11 #ifdef ALLOW_PTRACERS.h
23     #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    
39 adcroft 1.2 NAMELIST /OBCS_PARM01/
40     & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
41     & useOrlanskiNorth,useOrlanskiSouth,
42 heimbach 1.5 & useOrlanskiEast,useOrlanskiWest,
43     & OBNuFile,OBNvFile,OBNtFile,OBNsFile,
44     & OBSuFile,OBSvFile,OBStFile,OBSsFile,
45     & OBEuFile,OBEvFile,OBEtFile,OBEsFile,
46 heimbach 1.7 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,
47 mlosch 1.12 & useOBCSsponge, useOBCSbalance, useOBCSprescribe,
48     & OBCSprintDiags
49 mlosch 1.11 #ifdef ALLOW_PTRACERS
50     & , OBNptrFile,OBSptrFile,OBEptrFile,OBWptrFile
51     #endif
52 adcroft 1.3
53     #ifdef ALLOW_ORLANSKI
54     NAMELIST /OBCS_PARM02/
55 adcroft 1.6 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
56 adcroft 1.3 #endif
57 adcroft 1.2
58 heimbach 1.7 #ifdef ALLOW_OBCS_SPONGE
59     NAMELIST /OBCS_PARM03/
60     & Urelaxobcsinner,Urelaxobcsbound,
61     & Vrelaxobcsinner,Vrelaxobcsbound,
62     & spongeThickness
63     #endif
64    
65 jmc 1.13 _BEGIN_MASTER(myThid)
66 adcroft 1.2
67     C-- OBCS_READPARMS has been called so we know that
68     C the package is active.
69     OBCSIsOn=.TRUE.
70    
71     WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
72     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
73     & SQUEEZE_RIGHT , 1)
74    
75     CALL OPEN_COPY_DATA_FILE(
76     I 'data.obcs', 'OBCS_READPARMS',
77     O iUnit,
78     I myThid )
79    
80     C-- Default flags and values for OBCS
81     DO I=1,Nx
82     OB_Jnorth(I)=0
83     OB_Jsouth(I)=0
84     ENDDO
85     DO J=1,Ny
86     OB_Ieast(J)=0
87     OB_Iwest(J)=0
88     ENDDO
89     useOrlanskiNorth=.FALSE.
90     useOrlanskiSouth=.FALSE.
91     useOrlanskiEast =.FALSE.
92     useOrlanskiWest =.FALSE.
93 heimbach 1.7 useOBCSsponge =.FALSE.
94 mlosch 1.8 useOBCSbalance =.FALSE.
95 mlosch 1.12 useOBCSprescribe=.FALSE.
96     OBCSprintDiags =.TRUE.
97 heimbach 1.5
98     OBNuFile = ' '
99     OBNvFile = ' '
100     OBNtFile = ' '
101     OBNsFile = ' '
102     OBSuFile = ' '
103     OBSvFile = ' '
104     OBStFile = ' '
105     OBSsFile = ' '
106     OBEuFile = ' '
107     OBEvFile = ' '
108     OBEtFile = ' '
109     OBEsFile = ' '
110     OBWuFile = ' '
111     OBWvFile = ' '
112     OBWtFile = ' '
113     OBWsFile = ' '
114 mlosch 1.11 #ifdef ALLOW_PTRACERS
115     DO iTracer = 1, PTRACERS_num
116     OBNptrFile(iTracer) = ' '
117     OBSptrFile(iTracer) = ' '
118     OBEptrFile(iTracer) = ' '
119     OBWptrFile(iTracer) = ' '
120     ENDDO
121     #endif
122 adcroft 1.2
123     C-- Read parameters from open data file
124     READ(UNIT=iUnit,NML=OBCS_PARM01)
125    
126     C Account for periodicity if negative indices were supplied
127     DO J=1,Ny
128     IF (OB_Ieast(J).lt.0) OB_Ieast(J)=OB_Ieast(J)+Nx+1
129     ENDDO
130     DO I=1,Nx
131     IF (OB_Jnorth(I).lt.0) OB_Jnorth(I)=OB_Jnorth(I)+Ny+1
132     ENDDO
133 heimbach 1.4 write(*,*) 'OB Jn =',OB_Jnorth
134     write(*,*) 'OB Js =',OB_Jsouth
135     write(*,*) 'OB Ie =',OB_Ieast
136     write(*,*) 'OB Iw =',OB_Iwest
137 adcroft 1.2
138 adcroft 1.3 #ifdef ALLOW_ORLANSKI
139     C Default Orlanski radiation parameters
140     CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
141     cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed in sec. */
142 adcroft 1.6 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
143     useFixedCEast=.FALSE.
144     useFixedCWest=.FALSE.
145 adcroft 1.3 IF (useOrlanskiNorth.OR.
146     & useOrlanskiSouth.OR.
147     & useOrlanskiEast.OR.
148 jmc 1.13 & useOrlanskiWest)
149 adcroft 1.3 & READ(UNIT=iUnit,NML=OBCS_PARM02)
150 adcroft 1.2 #endif
151 jmc 1.13
152 heimbach 1.7 #ifdef ALLOW_OBCS_SPONGE
153 mlosch 1.10 C Default sponge layer parameters:
154     C sponge layer is turned off by default
155     spongeThickness = 0
156     Urelaxobcsinner = 0. _d 0
157     Urelaxobcsbound = 0. _d 0
158     Vrelaxobcsinner = 0. _d 0
159     Vrelaxobcsbound = 0. _d 0
160     CML this was the previous default in units of days
161     CML spongeThickness = 2
162     CML Urelaxobcsinner = 5. _d 0
163     CML Urelaxobcsbound = 1. _d 0
164     CML Vrelaxobcsinner = 5. _d 0
165     CML Vrelaxobcsbound = 1. _d 0
166 heimbach 1.7 IF (useOBCSsponge)
167     & READ(UNIT=iUnit,NML=OBCS_PARM03)
168     #endif
169    
170 adcroft 1.2 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
171     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
172     & SQUEEZE_RIGHT , 1)
173    
174     C-- Close the open data file
175     CLOSE(iUnit)
176     _END_MASTER(myThid)
177    
178     C-- Everyone else must wait for the parameters to be loaded
179     _BARRIER
180    
181     #endif /* ALLOW_OBCS */
182     RETURN
183     END

  ViewVC Help
Powered by ViewVC 1.1.22