/[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.7 - (hide annotations) (download)
Mon Sep 20 23:22:57 2004 UTC (20 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55a_post
Changes since 1.6: +23 -4 lines
o merged code to
  * prescribe/read time-dependent open boundaries
    (works in conjunction with exf, cal)
  * sponge layer code for open boundaries
  * each boundary N/S/E/W now has its own CPP option
    (healthy for the adjoint)

1 heimbach 1.7 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.5.6.1 2002/02/05 20:23:59 heimbach Exp $
2     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    
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 heimbach 1.5 & useOrlanskiEast,useOrlanskiWest,
32     & OBNuFile,OBNvFile,OBNtFile,OBNsFile,
33     & OBSuFile,OBSvFile,OBStFile,OBSsFile,
34     & OBEuFile,OBEvFile,OBEtFile,OBEsFile,
35 heimbach 1.7 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,
36     & useOBCSsponge
37 adcroft 1.3
38     #ifdef ALLOW_ORLANSKI
39     NAMELIST /OBCS_PARM02/
40 adcroft 1.6 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
41 adcroft 1.3 #endif
42 adcroft 1.2
43 heimbach 1.7 #ifdef ALLOW_OBCS_SPONGE
44     NAMELIST /OBCS_PARM03/
45     & Urelaxobcsinner,Urelaxobcsbound,
46     & Vrelaxobcsinner,Vrelaxobcsbound,
47     & spongeThickness
48     #endif
49    
50 adcroft 1.2 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 heimbach 1.7 useOBCSsponge =.FALSE.
86 heimbach 1.5
87     OBNuFile = ' '
88     OBNvFile = ' '
89     OBNtFile = ' '
90     OBNsFile = ' '
91     OBSuFile = ' '
92     OBSvFile = ' '
93     OBStFile = ' '
94     OBSsFile = ' '
95     OBEuFile = ' '
96     OBEvFile = ' '
97     OBEtFile = ' '
98     OBEsFile = ' '
99     OBWuFile = ' '
100     OBWvFile = ' '
101     OBWtFile = ' '
102     OBWsFile = ' '
103 adcroft 1.2
104     C-- Read parameters from open data file
105     READ(UNIT=iUnit,NML=OBCS_PARM01)
106    
107     C Account for periodicity if negative indices were supplied
108     DO J=1,Ny
109     IF (OB_Ieast(J).lt.0) OB_Ieast(J)=OB_Ieast(J)+Nx+1
110     ENDDO
111     DO I=1,Nx
112     IF (OB_Jnorth(I).lt.0) OB_Jnorth(I)=OB_Jnorth(I)+Ny+1
113     ENDDO
114 heimbach 1.4 write(*,*) 'OB Jn =',OB_Jnorth
115     write(*,*) 'OB Js =',OB_Jsouth
116     write(*,*) 'OB Ie =',OB_Ieast
117     write(*,*) 'OB Iw =',OB_Iwest
118 adcroft 1.2
119 adcroft 1.3 #ifdef ALLOW_ORLANSKI
120     C Default Orlanski radiation parameters
121     CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
122     cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed in sec. */
123 adcroft 1.6 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
124     useFixedCEast=.FALSE.
125     useFixedCWest=.FALSE.
126 adcroft 1.3 IF (useOrlanskiNorth.OR.
127     & useOrlanskiSouth.OR.
128     & useOrlanskiEast.OR.
129     & useOrlanskiWest)
130     & READ(UNIT=iUnit,NML=OBCS_PARM02)
131 adcroft 1.2 #endif
132 adcroft 1.3
133 heimbach 1.7 #ifdef ALLOW_OBCS_SPONGE
134     C Default sponge layer parameters
135     spongeThickness = 2
136     Urelaxobcsinner = 5. _d 0
137     Urelaxobcsbound = 1. _d 0
138     Vrelaxobcsinner = 5. _d 0
139     Vrelaxobcsbound = 1. _d 0
140     IF (useOBCSsponge)
141     & READ(UNIT=iUnit,NML=OBCS_PARM03)
142     #endif
143    
144 adcroft 1.2 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
145     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
146     & SQUEEZE_RIGHT , 1)
147    
148     C-- Close the open data file
149     CLOSE(iUnit)
150     _END_MASTER(myThid)
151    
152     C-- Everyone else must wait for the parameters to be loaded
153     _BARRIER
154    
155     #endif /* ALLOW_OBCS */
156     RETURN
157     END

  ViewVC Help
Powered by ViewVC 1.1.22