/[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.5 - (hide annotations) (download)
Wed Oct 19 01:28:45 2011 UTC (12 years, 8 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g
Changes since 1.4: +3 -2 lines
Include potential density as new coordinate (Thanks to David Munday)

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

  ViewVC Help
Powered by ViewVC 1.1.22