/[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.4 - (hide annotations) (download)
Thu Dec 16 00:56:48 2010 UTC (13 years, 6 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.3: +3 -2 lines
Add run-time flag to use bolus transport or not when available

1 dfer 1.4 C $Header: /u/gcmpack/MITgcm/pkg/layers/layers_readparms.F,v 1.3 2010/12/04 23:50:32 dfer Exp $
2 rpa 1.1 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 dfer 1.3 & layers_G, layers_taveFreq, layers_diagFreq,
26 dfer 1.4 & LAYER_nb, useBOLUS
27 rpa 1.1
28     C === Local variables ===
29     C msgBuf - Informational/error meesage buffer
30     C iUnit - Work variable for IO unit number
31     C k - index
32     CHARACTER*(MAX_LEN_MBUF) msgBuf
33     INTEGER iUnit, k
34    
35     _BEGIN_MASTER(myThid)
36    
37     C-- Default values for LAYERS
38    
39     C The MNC stuff is not working yet
40     layers_MNC = .FALSE.
41     layers_MDSIO = .TRUE.
42    
43     DO k=1,Nlayers+1
44     layers_G(k) = UNSET_RL
45     ENDDO
46 dfer 1.2 layers_taveFreq = taveFreq
47     layers_diagFreq = dumpFreq
48 dfer 1.3 LAYER_nb = 1
49 dfer 1.4 useBOLUS = .TRUE.
50 rpa 1.1
51     WRITE(msgBuf,'(A)') 'LAYERS_READPARMS: opening data.layers'
52     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
53     & SQUEEZE_RIGHT , 1)
54     CALL OPEN_COPY_DATA_FILE(
55     I 'data.layers', 'LAYERS_READPARMS',
56     O iUnit,
57     I myThid )
58    
59     C Read parameters from open data file
60     READ(UNIT=iUnit,NML=LAYERS_PARM01)
61     WRITE(msgBuf,'(A)')
62     & 'LAYERS_READPARMS: finished reading data.layers'
63     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
64     & SQUEEZE_RIGHT , 1)
65     C Close the open data file
66     CLOSE(iUnit)
67    
68     C-- Make sure the layers_G we just read is big enough
69     DO k=1,Nlayers+1
70     IF ( layers_G(k) .EQ. UNSET_RL ) THEN
71     WRITE(msgBuf,'(A,I4)')
72     & 'S/R LAYERS_READPARMS: No value for layers_G at k =', k
73     CALL PRINT_ERROR( msgBuf, myThid )
74     STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
75     ELSE IF ( k .EQ. 1 ) THEN
76     C Do nothing
77     ELSE IF ( layers_G(k) .LE. layers_G(k-1) ) THEN
78     C Check to make sure layers_G is increasing
79     WRITE(msgBuf,'(A,I4)')
80     & 'S/R LAYERS_READPARMS: layers_G is not increasing at k =', k
81     CALL PRINT_ERROR( msgBuf, myThid )
82     STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
83     ENDIF
84     ENDDO
85    
86     C-- Make sure that we locally honor the global MNC on/off flag
87     layers_MNC = layers_MNC .AND. useMNC
88     #ifndef ALLOW_MNC
89     C Fix to avoid running without getting any output:
90     layers_MNC = .FALSE.
91     #endif
92     layers_MDSIO = (.NOT. layers_MNC) .OR. outputTypesInclusive
93    
94     _END_MASTER(myThid)
95    
96     C-- Everyone else must wait for the parameters to be loaded
97     _BARRIER
98    
99     #endif /* ALLOW_MYPACKAGE */
100    
101     RETURN
102     END

  ViewVC Help
Powered by ViewVC 1.1.22