/[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.11 - (hide annotations) (download)
Mon Oct 10 05:53:48 2005 UTC (18 years, 7 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint57y_post, checkpoint58, checkpoint58a_post, checkpoint57z_post, checkpoint57v_post, checkpoint57y_pre, checkpint57u_post, checkpoint57w_post, checkpoint57x_post, checkpoint58c_post
Changes since 1.10: +17 -2 lines
o OBCS and PTRACERS: add open boundary support for passive tracers
  - either use homogenous (pseudo) v.Neumann conditions or prescribe
    OB-values from file; this is not different from the way theta and salinity
    are treated
  - however, Orlanski-radiation conditions are not supported, and the model
    will stop if you use pTracers and Orlanski at the same time.
  - beefed up the rountine obcs_external_fields_load: now only those open
    boundary values are overwritten with values from files for which there
    are really files, otherwise the OB-fields remain untouched. This makes
    it possible to use different OBs at different ends of the domain (as
    with EXF)
  - TODO: add support for OB?w and OB?eta, which can currently not be read
    from a file.

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

  ViewVC Help
Powered by ViewVC 1.1.22