/[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.2 - (show annotations) (download)
Fri Feb 2 21:36:30 2001 UTC (23 years, 4 months ago) by adcroft
Branch: MAIN
Changes since 1.1: +117 -0 lines
Merged changes from branch "branch-atmos-merge" into MAIN (checkpoint34)
 - substantial modifications to algorithm sequence (dynamics.F)
 - packaged OBCS, Shapiro filter, Zonal filter, Atmospheric Physics

1 C $Header: /u/gcmpack/models/MITgcmUV/pkg/obcs/Attic/obcs_readparms.F,v 1.1.2.1 2001/01/30 21:03:00 adcroft Exp $
2 C $Name: branch-atmos-merge-freeze $
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 _RL Orlanski_Cmax,Orlanski_TimeScale
29 NAMELIST /OBCS_PARM01/
30 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
31 & useOrlanskiNorth,useOrlanskiSouth,
32 & useOrlanskiEast,useOrlanskiWest,
33 & Orlanski_Cmax,Orlanski_TimeScale
34
35 C === Local variables ===
36 C msgBuf - Informational/error meesage buffer
37 C iUnit - Work variable for IO unit number
38 CHARACTER*(MAX_LEN_MBUF) msgBuf
39 INTEGER iUnit
40 INTEGER I,J
41
42 C-- OBCS_READPARMS has been called so we know that
43 C the package is active.
44 OBCSIsOn=.TRUE.
45
46 _BEGIN_MASTER(myThid)
47
48 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
49 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
50 & SQUEEZE_RIGHT , 1)
51
52 CALL OPEN_COPY_DATA_FILE(
53 I 'data.obcs', 'OBCS_READPARMS',
54 O iUnit,
55 I myThid )
56
57 C-- Default flags and values for OBCS
58 DO I=1,Nx
59 OB_Jnorth(I)=0
60 OB_Jsouth(I)=0
61 ENDDO
62 DO J=1,Ny
63 OB_Ieast(J)=0
64 OB_Iwest(J)=0
65 ENDDO
66 useOrlanskiNorth=.FALSE.
67 useOrlanskiSouth=.FALSE.
68 useOrlanskiEast =.FALSE.
69 useOrlanskiWest =.FALSE.
70
71 C-- Defaults for the Orlanksi package
72 Orlanski_Cmax=0.
73 Orlanski_TimeScale=0.
74
75 C-- Read parameters from open data file
76 READ(UNIT=iUnit,NML=OBCS_PARM01)
77
78 C Account for periodicity if negative indices were supplied
79 DO J=1,Ny
80 IF (OB_Ieast(J).lt.0) OB_Ieast(J)=OB_Ieast(J)+Nx+1
81 ENDDO
82 DO I=1,Nx
83 IF (OB_Jnorth(I).lt.0) OB_Jnorth(I)=OB_Jnorth(I)+Ny+1
84 ENDDO
85 write(0,*) 'OB Jn =',OB_Jnorth
86 write(0,*) 'OB Js =',OB_Jsouth
87 write(0,*) 'OB Ie =',OB_Ieast
88 write(0,*) 'OB Iw =',OB_Iwest
89
90 #ifndef ALLOW_ORLANSKI
91 IF (
92 & Orlanski_Cmax.NE.0. .OR.
93 & Orlanski_TimeScale.NE.0.) THEN
94 WRITE(msgBuf,'(A)')
95 & 'OBCS_READPARMS: Orlanski parameters were set!'
96 CALL PRINT_ERROR( msgBuf, 1)
97 STOP 'OBCS_READPARMS: Inconsistent CPP options and parameters'
98 ENDIF
99 #else
100 Cmax=Orlanski_Cmax
101 cVelTimeScale=Orlanski_TimeScale
102 #endif
103
104 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
105 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
106 & SQUEEZE_RIGHT , 1)
107
108 C-- Close the open data file
109 CLOSE(iUnit)
110 _END_MASTER(myThid)
111
112 C-- Everyone else must wait for the parameters to be loaded
113 _BARRIER
114
115 #endif /* ALLOW_OBCS */
116 RETURN
117 END

  ViewVC Help
Powered by ViewVC 1.1.22