/[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.6 - (show annotations) (download)
Tue Jul 6 18:25:52 2004 UTC (21 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint54d_post, checkpoint54e_post, checkpoint55, checkpoint54f_post, checkpoint54b_post, checkpoint54c_post
Changes since 1.5: +7 -3 lines
Modifications from Sonya Legg, James Girton and Ulriker Riemenscheider
pertaining to Orlanski radiation conditions for salt
 o NOTE these are only for eastern and western boundaries; someone needs
   to duplicate these mods for the northwen and southern boudnaries

1 C $Header: /u/u0/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.5 2001/05/14 21:36:45 heimbach Exp $
2 C $Name: release1_p5 $
3 cc
4
5 #include "OBCS_OPTIONS.h"
6
7 SUBROUTINE OBCS_READPARMS( myThid )
8 C /==========================================================\
9 C | SUBROUTINE OBCS_READPARMS |
10 C | o Routine to initialize OBCS variables and constants. |
11 C |==========================================================|
12 C \==========================================================/
13 IMPLICIT NONE
14
15 C === Global variables ===
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "OBCS.h"
20 #ifdef ALLOW_ORLANSKI
21 #include "ORLANSKI.h"
22 #endif
23
24 C === Routine arguments ===
25 INTEGER myThid
26
27 #ifdef ALLOW_OBCS
28
29 NAMELIST /OBCS_PARM01/
30 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
31 & useOrlanskiNorth,useOrlanskiSouth,
32 & useOrlanskiEast,useOrlanskiWest,
33 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,
34 & OBSuFile,OBSvFile,OBStFile,OBSsFile,
35 & OBEuFile,OBEvFile,OBEtFile,OBEsFile,
36 & OBWuFile,OBWvFile,OBWtFile,OBWsFile
37
38 #ifdef ALLOW_ORLANSKI
39 NAMELIST /OBCS_PARM02/
40 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
41 #endif
42
43 C === Local variables ===
44 C msgBuf - Informational/error meesage buffer
45 C iUnit - Work variable for IO unit number
46 CHARACTER*(MAX_LEN_MBUF) msgBuf
47 INTEGER iUnit
48 INTEGER I,J
49
50 C-- OBCS_READPARMS has been called so we know that
51 C the package is active.
52 OBCSIsOn=.TRUE.
53
54 _BEGIN_MASTER(myThid)
55
56 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
57 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
58 & SQUEEZE_RIGHT , 1)
59
60 CALL OPEN_COPY_DATA_FILE(
61 I 'data.obcs', 'OBCS_READPARMS',
62 O iUnit,
63 I myThid )
64
65 C-- Default flags and values for OBCS
66 DO I=1,Nx
67 OB_Jnorth(I)=0
68 OB_Jsouth(I)=0
69 ENDDO
70 DO J=1,Ny
71 OB_Ieast(J)=0
72 OB_Iwest(J)=0
73 ENDDO
74 useOrlanskiNorth=.FALSE.
75 useOrlanskiSouth=.FALSE.
76 useOrlanskiEast =.FALSE.
77 useOrlanskiWest =.FALSE.
78
79 OBNuFile = ' '
80 OBNvFile = ' '
81 OBNtFile = ' '
82 OBNsFile = ' '
83 OBSuFile = ' '
84 OBSvFile = ' '
85 OBStFile = ' '
86 OBSsFile = ' '
87 OBEuFile = ' '
88 OBEvFile = ' '
89 OBEtFile = ' '
90 OBEsFile = ' '
91 OBWuFile = ' '
92 OBWvFile = ' '
93 OBWtFile = ' '
94 OBWsFile = ' '
95
96 C-- Read parameters from open data file
97 READ(UNIT=iUnit,NML=OBCS_PARM01)
98
99 C Account for periodicity if negative indices were supplied
100 DO J=1,Ny
101 IF (OB_Ieast(J).lt.0) OB_Ieast(J)=OB_Ieast(J)+Nx+1
102 ENDDO
103 DO I=1,Nx
104 IF (OB_Jnorth(I).lt.0) OB_Jnorth(I)=OB_Jnorth(I)+Ny+1
105 ENDDO
106 write(*,*) 'OB Jn =',OB_Jnorth
107 write(*,*) 'OB Js =',OB_Jsouth
108 write(*,*) 'OB Ie =',OB_Ieast
109 write(*,*) 'OB Iw =',OB_Iwest
110
111 #ifdef ALLOW_ORLANSKI
112 C Default Orlanski radiation parameters
113 CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
114 cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed in sec. */
115 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
116 useFixedCEast=.FALSE.
117 useFixedCWest=.FALSE.
118 IF (useOrlanskiNorth.OR.
119 & useOrlanskiSouth.OR.
120 & useOrlanskiEast.OR.
121 & useOrlanskiWest)
122 & READ(UNIT=iUnit,NML=OBCS_PARM02)
123 #endif
124
125 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
126 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
127 & SQUEEZE_RIGHT , 1)
128
129 C-- Close the open data file
130 CLOSE(iUnit)
131 _END_MASTER(myThid)
132
133 C-- Everyone else must wait for the parameters to be loaded
134 _BARRIER
135
136 #endif /* ALLOW_OBCS */
137 RETURN
138 END

  ViewVC Help
Powered by ViewVC 1.1.22