/[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.2 - (hide annotations) (download)
Wed Sep 30 15:58:29 2009 UTC (14 years, 7 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.1: +4 -2 lines
- introduce tave and dump frequencies specific to the package
- fix timeave outputs

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

  ViewVC Help
Powered by ViewVC 1.1.22