/[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.3 - (hide annotations) (download)
Sat Dec 4 23:50:32 2010 UTC (13 years, 6 months ago) by dfer
Branch: MAIN
Changes since 1.2: +4 -2 lines
Some extensions:
- if GM with advective form is on, its transport is included,
- a flag to choose between temperature and salt as possible binning tracers

1 dfer 1.3 C $Header: /u/gcmpack/MITgcm/pkg/layers/layers_readparms.F,v 1.2 2009/09/30 15:58:29 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     & LAYER_nb
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 rpa 1.1
50     WRITE(msgBuf,'(A)') 'LAYERS_READPARMS: opening data.layers'
51     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
52     & SQUEEZE_RIGHT , 1)
53     CALL OPEN_COPY_DATA_FILE(
54     I 'data.layers', 'LAYERS_READPARMS',
55     O iUnit,
56     I myThid )
57    
58     C Read parameters from open data file
59     READ(UNIT=iUnit,NML=LAYERS_PARM01)
60     WRITE(msgBuf,'(A)')
61     & 'LAYERS_READPARMS: finished reading data.layers'
62     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
63     & SQUEEZE_RIGHT , 1)
64     C Close the open data file
65     CLOSE(iUnit)
66    
67     C-- Make sure the layers_G we just read is big enough
68     DO k=1,Nlayers+1
69     IF ( layers_G(k) .EQ. UNSET_RL ) THEN
70     WRITE(msgBuf,'(A,I4)')
71     & 'S/R LAYERS_READPARMS: No value for layers_G at k =', k
72     CALL PRINT_ERROR( msgBuf, myThid )
73     STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
74     ELSE IF ( k .EQ. 1 ) THEN
75     C Do nothing
76     ELSE IF ( layers_G(k) .LE. layers_G(k-1) ) THEN
77     C Check to make sure layers_G is increasing
78     WRITE(msgBuf,'(A,I4)')
79     & 'S/R LAYERS_READPARMS: layers_G is not increasing at k =', k
80     CALL PRINT_ERROR( msgBuf, myThid )
81     STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
82     ENDIF
83     ENDDO
84    
85     C-- Make sure that we locally honor the global MNC on/off flag
86     layers_MNC = layers_MNC .AND. useMNC
87     #ifndef ALLOW_MNC
88     C Fix to avoid running without getting any output:
89     layers_MNC = .FALSE.
90     #endif
91     layers_MDSIO = (.NOT. layers_MNC) .OR. outputTypesInclusive
92    
93     _END_MASTER(myThid)
94    
95     C-- Everyone else must wait for the parameters to be loaded
96     _BARRIER
97    
98     #endif /* ALLOW_MYPACKAGE */
99    
100     RETURN
101     END

  ViewVC Help
Powered by ViewVC 1.1.22