/[MITgcm]/MITgcm/pkg/layers/layers_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/layers/layers_readparms.F

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


Revision 1.1 - (hide annotations) (download)
Wed Sep 16 21:25:47 2009 UTC (14 years, 9 months ago) by rpa
Branch: MAIN
CVS Tags: checkpoint61v
Merge layers package into the main source

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

  ViewVC Help
Powered by ViewVC 1.1.22