/[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.12 - (show annotations) (download)
Tue Apr 4 07:46:17 2006 UTC (19 years, 3 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58f_post, checkpoint58d_post, checkpoint58m_post, checkpoint58o_post, checkpoint58p_post, checkpoint58e_post, checkpoint58n_post, checkpoint58k_post, checkpoint58l_post, checkpoint58g_post, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post
Changes since 1.11: +5 -3 lines
add a flag OBCSprintDiags (default = true) that allows me to turn off
the eccessive output to STDOUT that this package produces

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.11 2005/10/10 05:53:48 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.h
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 NAMELIST /OBCS_PARM01/
33 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
34 & useOrlanskiNorth,useOrlanskiSouth,
35 & useOrlanskiEast,useOrlanskiWest,
36 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,
37 & OBSuFile,OBSvFile,OBStFile,OBSsFile,
38 & OBEuFile,OBEvFile,OBEtFile,OBEsFile,
39 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,
40 & useOBCSsponge, useOBCSbalance, useOBCSprescribe,
41 & OBCSprintDiags
42 #ifdef ALLOW_PTRACERS
43 & , OBNptrFile,OBSptrFile,OBEptrFile,OBWptrFile
44 #endif
45
46 #ifdef ALLOW_ORLANSKI
47 NAMELIST /OBCS_PARM02/
48 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
49 #endif
50
51 #ifdef ALLOW_OBCS_SPONGE
52 NAMELIST /OBCS_PARM03/
53 & Urelaxobcsinner,Urelaxobcsbound,
54 & Vrelaxobcsinner,Vrelaxobcsbound,
55 & spongeThickness
56 #endif
57
58 C === Local variables ===
59 C msgBuf - Informational/error meesage buffer
60 C iUnit - Work variable for IO unit number
61 CHARACTER*(MAX_LEN_MBUF) msgBuf
62 INTEGER iUnit
63 INTEGER I,J,iTracer
64
65 C-- OBCS_READPARMS has been called so we know that
66 C the package is active.
67 OBCSIsOn=.TRUE.
68
69 _BEGIN_MASTER(myThid)
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 useOBCSsponge =.FALSE.
94 useOBCSbalance =.FALSE.
95 useOBCSprescribe=.FALSE.
96 OBCSprintDiags =.TRUE.
97
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 #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
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 write(*,*) 'OB Jn =',OB_Jnorth
134 write(*,*) 'OB Js =',OB_Jsouth
135 write(*,*) 'OB Ie =',OB_Ieast
136 write(*,*) 'OB Iw =',OB_Iwest
137
138 #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 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
143 useFixedCEast=.FALSE.
144 useFixedCWest=.FALSE.
145 IF (useOrlanskiNorth.OR.
146 & useOrlanskiSouth.OR.
147 & useOrlanskiEast.OR.
148 & useOrlanskiWest)
149 & READ(UNIT=iUnit,NML=OBCS_PARM02)
150 #endif
151
152 #ifdef ALLOW_OBCS_SPONGE
153 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 IF (useOBCSsponge)
167 & READ(UNIT=iUnit,NML=OBCS_PARM03)
168 #endif
169
170 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