/[MITgcm]/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_exch2_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_exch2_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.3 - (hide annotations) (download)
Wed Sep 28 20:52:22 2005 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +5 -2 lines
 o adding corner data

1 edhill 1.3 C $Header: /u/gcmpack/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_exch2_readparms.F,v 1.2 2005/09/24 19:38:18 edhill Exp $
2 edhill 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP
8     C !ROUTINE: W2_EXCH2_READPARMS
9    
10     C !INTERFACE:
11     SUBROUTINE W2_EXCH2_READPARMS
12    
13     C !DESCRIPTION:
14     C Read the EXCH2 namelist file.
15    
16     C !USES:
17     IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "EESUPPORT.h"
21     #include "W2_EXCH2_TOPOLOGY.h"
22     #include "W2_EXCH2_PARAMS.h"
23     INTEGER IFNBLNK
24     EXTERNAL IFNBLNK
25     INTEGER ILNBLNK
26     EXTERNAL ILNBLNK
27     CEOP
28    
29     C !LOCAL VARIABLES:
30     C iUnit :: Work variable for IO unit number
31     C errIO :: IO unit error flag
32     C IL :: Temp. for index strings
33     C msgBuf :: Temp. for textual I/O
34     C record :: Temp. for textual I/O
35     INTEGER IL
36     INTEGER errIO
37     INTEGER iUnit
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39     CHARACTER*(MAX_LEN_PREC) record
40     NAMELIST /EXCH2/
41 edhill 1.3 & W2_read_acsii_topo, W2_atopo_fname, W2_atopo_oname,
42     & W2_atopo_o_ver, W2_use_GEx_corners
43 edhill 1.1
44     W2_read_acsii_topo = .FALSE.
45     W2_atopo_fname = 'w2_topo.txt'
46 edhill 1.2 W2_atopo_oname = 'w2_topo.log'
47 edhill 1.3 W2_atopo_o_ver = '001'
48     W2_use_GEx_corners = .FALSE.
49 edhill 1.1
50     C Read in data from "data.exch2" file: note that most of the
51     C following is an exact cut-and-paste from "eeset_parms.F"
52    
53     C Make scratch copies of input data file with and without comments
54     #ifdef TARGET_BGL
55     OPEN(UNIT=scrUnit1,FILE='scratch1',STATUS='UNKNOWN')
56     OPEN(UNIT=scrUnit2,FILE='scratch2',STATUS='UNKNOWN')
57     #else
58     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
59     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
60     #endif
61     OPEN(UNIT=eeDataUnit,FILE='data.exch2',STATUS='OLD',
62     & err=1,IOSTAT=errIO)
63     IF ( errIO .GE. 0 ) GOTO 2
64     1 CONTINUE
65     WRITE(msgBuf,'(A)')
66     & 'S/R W2_EXCH2_READPARMS'
67     CALL PRINT_ERROR( msgBuf , 1)
68     WRITE(msgBuf,'(A)')
69     & 'Unable to open execution environment'
70     CALL PRINT_ERROR( msgBuf , 1)
71     WRITE(msgBuf,'(A)')
72     & 'parameter file "data.exch2"'
73     CALL PRINT_ERROR( msgBuf , 1)
74     STOP 'ABNORMAL END: S/R W2_EXCH2_READPARMS'
75     2 CONTINUE
76     1000 CONTINUE
77     READ(eeDataUnit,FMT='(A)',END=1001) RECORD
78     IL = MAX(ILNBLNK(RECORD),1)
79     IF ( RECORD(1:1) .NE. commentCharacter ) THEN
80     CALL NML_SET_TERMINATOR( RECORD )
81     WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
82     ENDIF
83     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
84     GOTO 1000
85     1001 CONTINUE
86     CLOSE(eeDataUnit)
87     C-- Report contents of parameter file
88     WRITE(msgBuf,'(A)')
89     & '// ======================================================='
90     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
91     WRITE(msgBuf,'(A)')
92     & '// EXCH2 parameter file "data.exch2"'
93     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
94     WRITE(msgBuf,'(A)')
95     & '// ======================================================='
96     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
97     & SQUEEZE_RIGHT , 1)
98    
99     iUnit = scrUnit2
100     REWIND(iUnit)
101     2000 CONTINUE
102     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
103     IL = MAX(ILNBLNK(RECORD),1)
104     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
105     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT , 1)
106     GOTO 2000
107     2001 CONTINUE
108     CLOSE(iUnit)
109    
110     WRITE(msgBuf,'(A)') ' '
111     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
112     & SQUEEZE_RIGHT , 1)
113    
114     iUnit = scrUnit1
115     REWIND(iUnit)
116     READ(UNIT=iUnit,NML=EXCH2,IOSTAT=errIO,err=3)
117     IF ( errIO .GE. 0 ) GOTO 4
118     3 CONTINUE
119     #ifndef TARGET_PWR3
120     WRITE(msgBuf,'(A)')
121     & 'S/R W2_EXCH2_READPARMS'
122     CALL PRINT_ERROR( msgBuf , 1)
123     WRITE(msgBuf,'(A)')
124     & 'Error reading execution environment '
125     CALL PRINT_ERROR( msgBuf , 1)
126     WRITE(msgBuf,'(A)')
127     & 'parameter file "eedata"'
128     CALL PRINT_ERROR( msgBuf , 1)
129     CALL EEDATA_EXAMPLE
130     STOP 'ABNORMAL END: S/R W2_EXCH2_READPARMS'
131     #endif
132     4 CONTINUE
133    
134     C-- Execution Environment parameter file read
135     CLOSE(iUnit)
136    
137     RETURN
138     END

  ViewVC Help
Powered by ViewVC 1.1.22