/[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.18 - (hide annotations) (download)
Thu Jan 24 18:39:38 2008 UTC (17 years, 6 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint59p, checkpoint59o, checkpoint59n
Changes since 1.17: +11 -10 lines
o pkg/obcs/exf: add useOBCSYearlyFields (=.FALSE.) to obcs with exf in
  analogy to useExfYearlyFields; rearrange obcs_prescribe_read: two new
  subroutines (which could be generated from a template, because they are
  almost identical) to save a few lines of code and may make it easier to
  change this bit; for now they are included in obcs_prescribe_read.F for
  simplicity

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

  ViewVC Help
Powered by ViewVC 1.1.22