/[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.9 - (show annotations) (download)
Wed Sep 22 20:44:37 2004 UTC (19 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55c_post
Changes since 1.8: +3 -2 lines
new useOBCS flags and re-arranged obcs_calc

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.8 2004/09/22 06:30:56 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
23 C === Routine arguments ===
24 INTEGER myThid
25
26 #ifdef ALLOW_OBCS
27
28 NAMELIST /OBCS_PARM01/
29 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
30 & useOrlanskiNorth,useOrlanskiSouth,
31 & useOrlanskiEast,useOrlanskiWest,
32 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,
33 & OBSuFile,OBSvFile,OBStFile,OBSsFile,
34 & OBEuFile,OBEvFile,OBEtFile,OBEsFile,
35 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,
36 & useOBCSsponge, useOBCSbalance, useOBCSprescribe
37
38 #ifdef ALLOW_ORLANSKI
39 NAMELIST /OBCS_PARM02/
40 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
41 #endif
42
43 #ifdef ALLOW_OBCS_SPONGE
44 NAMELIST /OBCS_PARM03/
45 & Urelaxobcsinner,Urelaxobcsbound,
46 & Vrelaxobcsinner,Vrelaxobcsbound,
47 & spongeThickness
48 #endif
49
50 C === Local variables ===
51 C msgBuf - Informational/error meesage buffer
52 C iUnit - Work variable for IO unit number
53 CHARACTER*(MAX_LEN_MBUF) msgBuf
54 INTEGER iUnit
55 INTEGER I,J
56
57 C-- OBCS_READPARMS has been called so we know that
58 C the package is active.
59 OBCSIsOn=.TRUE.
60
61 _BEGIN_MASTER(myThid)
62
63 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
64 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65 & SQUEEZE_RIGHT , 1)
66
67 CALL OPEN_COPY_DATA_FILE(
68 I 'data.obcs', 'OBCS_READPARMS',
69 O iUnit,
70 I myThid )
71
72 C-- Default flags and values for OBCS
73 DO I=1,Nx
74 OB_Jnorth(I)=0
75 OB_Jsouth(I)=0
76 ENDDO
77 DO J=1,Ny
78 OB_Ieast(J)=0
79 OB_Iwest(J)=0
80 ENDDO
81 useOrlanskiNorth=.FALSE.
82 useOrlanskiSouth=.FALSE.
83 useOrlanskiEast =.FALSE.
84 useOrlanskiWest =.FALSE.
85 useOBCSsponge =.FALSE.
86 useOBCSbalance =.FALSE.
87 useOBCSprescribe = .FALSE.
88
89 OBNuFile = ' '
90 OBNvFile = ' '
91 OBNtFile = ' '
92 OBNsFile = ' '
93 OBSuFile = ' '
94 OBSvFile = ' '
95 OBStFile = ' '
96 OBSsFile = ' '
97 OBEuFile = ' '
98 OBEvFile = ' '
99 OBEtFile = ' '
100 OBEsFile = ' '
101 OBWuFile = ' '
102 OBWvFile = ' '
103 OBWtFile = ' '
104 OBWsFile = ' '
105
106 C-- Read parameters from open data file
107 READ(UNIT=iUnit,NML=OBCS_PARM01)
108
109 C Account for periodicity if negative indices were supplied
110 DO J=1,Ny
111 IF (OB_Ieast(J).lt.0) OB_Ieast(J)=OB_Ieast(J)+Nx+1
112 ENDDO
113 DO I=1,Nx
114 IF (OB_Jnorth(I).lt.0) OB_Jnorth(I)=OB_Jnorth(I)+Ny+1
115 ENDDO
116 write(*,*) 'OB Jn =',OB_Jnorth
117 write(*,*) 'OB Js =',OB_Jsouth
118 write(*,*) 'OB Ie =',OB_Ieast
119 write(*,*) 'OB Iw =',OB_Iwest
120
121 #ifdef ALLOW_ORLANSKI
122 C Default Orlanski radiation parameters
123 CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
124 cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed in sec. */
125 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
126 useFixedCEast=.FALSE.
127 useFixedCWest=.FALSE.
128 IF (useOrlanskiNorth.OR.
129 & useOrlanskiSouth.OR.
130 & useOrlanskiEast.OR.
131 & useOrlanskiWest)
132 & READ(UNIT=iUnit,NML=OBCS_PARM02)
133 #endif
134
135 #ifdef ALLOW_OBCS_SPONGE
136 C Default sponge layer parameters
137 spongeThickness = 2
138 Urelaxobcsinner = 5. _d 0
139 Urelaxobcsbound = 1. _d 0
140 Vrelaxobcsinner = 5. _d 0
141 Vrelaxobcsbound = 1. _d 0
142 IF (useOBCSsponge)
143 & READ(UNIT=iUnit,NML=OBCS_PARM03)
144 #endif
145
146 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
147 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
148 & SQUEEZE_RIGHT , 1)
149
150 C-- Close the open data file
151 CLOSE(iUnit)
152 _END_MASTER(myThid)
153
154 C-- Everyone else must wait for the parameters to be loaded
155 _BARRIER
156
157 #endif /* ALLOW_OBCS */
158 RETURN
159 END

  ViewVC Help
Powered by ViewVC 1.1.22