/[MITgcm]/MITgcm_contrib/rpa_layers/layers/layers_readparms.F
ViewVC logotype

Contents of /MITgcm_contrib/rpa_layers/layers/layers_readparms.F

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


Revision 1.1 - (show annotations) (download)
Tue Sep 15 19:16:53 2009 UTC (15 years, 10 months ago) by rpa
Branch: MAIN
importing layers package

1 #include "LAYERS_OPTIONS.h"
2
3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
4
5 SUBROUTINE LAYERS_READPARMS( myThid )
6
7 C Read LAYERS parameters from data file.
8
9 IMPLICIT NONE
10 #include "SIZE.h"
11 #include "EEPARAMS.h"
12 #include "PARAMS.h"
13 #include "LAYERS_SIZE.h"
14 #include "LAYERS.h"
15
16 C INPUT PARAMETERS:
17 INTEGER myThid
18
19 #ifdef ALLOW_LAYERS
20
21 NAMELIST /LAYERS_PARM01/
22 & layers_G
23
24 C === Local variables ===
25 C msgBuf - Informational/error meesage buffer
26 C iUnit - Work variable for IO unit number
27 C k - index
28 CHARACTER*(MAX_LEN_MBUF) msgBuf
29 INTEGER iUnit, k
30
31 _BEGIN_MASTER(myThid)
32
33 C-- Default values for LAYERS
34
35 C The MNC stuff is not working yet
36 layers_MNC = .FALSE.
37 layers_MDSIO = .TRUE.
38
39 DO k=1,Nlayers+1
40 layers_G(k) = UNSET_RL
41 ENDDO
42
43 WRITE(msgBuf,'(A)') 'LAYERS_READPARMS: opening data.layers'
44 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
45 & SQUEEZE_RIGHT , 1)
46 CALL OPEN_COPY_DATA_FILE(
47 I 'data.layers', 'LAYERS_READPARMS',
48 O iUnit,
49 I myThid )
50
51 C Read parameters from open data file
52 READ(UNIT=iUnit,NML=LAYERS_PARM01)
53 WRITE(msgBuf,'(A)')
54 & 'LAYERS_READPARMS: finished reading data.layers'
55 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
56 & SQUEEZE_RIGHT , 1)
57 C Close the open data file
58 CLOSE(iUnit)
59
60 C-- Make sure the layers_G we just read is big enough
61 DO k=1,Nlayers+1
62 IF ( layers_G(k) .EQ. UNSET_RL ) THEN
63 WRITE(msgBuf,'(A,I4)')
64 & 'S/R LAYERS_READPARMS: No value for layers_G at k =', k
65 CALL PRINT_ERROR( msgBuf, myThid )
66 STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
67 ELSE IF ( k .EQ. 1 ) THEN
68 C Do nothing
69 ELSE IF ( layers_G(k) .LE. layers_G(k-1) ) THEN
70 C Check to make sure layers_G is increasing
71 WRITE(msgBuf,'(A,I4)')
72 & 'S/R LAYERS_READPARMS: layers_G is not increasing at k =', k
73 CALL PRINT_ERROR( msgBuf, myThid )
74 STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
75 ENDIF
76 ENDDO
77
78 C-- Make sure that we locally honor the global MNC on/off flag
79 layers_MNC = layers_MNC .AND. useMNC
80 #ifndef ALLOW_MNC
81 C Fix to avoid running without getting any output:
82 layers_MNC = .FALSE.
83 #endif
84 layers_MDSIO = (.NOT. layers_MNC) .OR. outputTypesInclusive
85
86 _END_MASTER(myThid)
87
88 C-- Everyone else must wait for the parameters to be loaded
89 _BARRIER
90
91 #endif /* ALLOW_MYPACKAGE */
92
93 RETURN
94 END

  ViewVC Help
Powered by ViewVC 1.1.22