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

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

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


Revision 1.6 - (show annotations) (download)
Wed Sep 19 18:48:18 2012 UTC (11 years, 9 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64b, checkpoint64
Changes since 1.5: +72 -12 lines
- added layers_maxNum dimension, to allow for multiple layers
  computations at once (if layers_maxNum >1 in LAYERS_SIZE.h).
- added/replaced new run time parameters :
  layers_bounds (repl. layers_G), layers_bolus (repl. useBOLUS),
  layers_num (repl. LAYER_nb; set by run time layers_name),
  layers_name ('TH', 'SLT' or 'RHO'), layers_krho (repl. layers_kref)
- The old way of specifying LAYER_nb, layers_G, etc. is kept
  for backward compatibility, and superseeds the new way. For now.
- layers_G.data output is replaced with layers1SLT.data
  where '1' is the layers set index (.LE.layers_maxNum)
  and 'SLT' is layers_name (i.e. the type of layers).
- Typical diagnostics names : 'LaUH1SLT','LaHw1SLT'.
- bug fix : previous commit was missing a pair of bi,bj loops.
- added ALLOW_LAYERS_OUTPUT cpp option : if undef then comment
  out the old fashion way of output (that still works for the
  first set of layers). Prefered way now is via pkg/diagnostics.

1 C $Header: /u/gcmpack/MITgcm/pkg/layers/layers_readparms.F,v 1.5 2011/10/19 01:28:45 dfer 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, layers_taveFreq, layers_diagFreq,
26 & LAYER_nb, layers_kref, useBOLUS, layers_bolus,
27 & layers_name, layers_bounds, layers_krho
28
29 C === Local variables ===
30 C msgBuf - Informational/error meesage buffer
31 C iUnit - Work variable for IO unit number
32 C k - index
33 CHARACTER*(MAX_LEN_MBUF) msgBuf
34 INTEGER iUnit, k, iLa
35
36 _BEGIN_MASTER(myThid)
37
38 C-- Default values for LAYERS
39
40 C The MNC stuff is not working yet
41 layers_MNC = .FALSE.
42 layers_MDSIO = .TRUE.
43
44 DO iLa=1,layers_maxNum
45 layers_name(iLa) = ' '
46 layers_num(iLa) = 0
47 layers_krho(iLa)= 1
48 layers_bolus(iLa) = .TRUE.
49 DO k=1,Nlayers+1
50 layers_bounds(k,iLa) = UNSET_RL
51 ENDDO
52 ENDDO
53
54 DO k=1,Nlayers+1
55 layers_G(k) = UNSET_RL
56 ENDDO
57 layers_taveFreq = taveFreq
58 layers_diagFreq = dumpFreq
59 LAYER_nb = 0
60 layers_kref = 1
61 useBOLUS = .TRUE.
62
63 WRITE(msgBuf,'(A)') 'LAYERS_READPARMS: opening data.layers'
64 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65 & SQUEEZE_RIGHT , 1)
66 CALL OPEN_COPY_DATA_FILE(
67 I 'data.layers', 'LAYERS_READPARMS',
68 O iUnit,
69 I myThid )
70
71
72 C Read parameters from open data file
73 READ(UNIT=iUnit,NML=LAYERS_PARM01)
74 WRITE(msgBuf,'(A)')
75 & 'LAYERS_READPARMS: finished reading data.layers'
76 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
77 & SQUEEZE_RIGHT , 1)
78 C Close the open data file
79 CLOSE(iUnit)
80
81 c revert to old approach
82 c (unless I simply retore the old ways, I need a
83 c print statement or two as I override the new way)
84 IF ( LAYER_nb.NE.0 ) THEN
85 layers_num(1) = LAYER_nb
86 layers_krho(1) = layers_kref
87 layers_bolus(iLa) = useBOLUS
88 DO k=1,Nlayers+1
89 layers_bounds(k,1) = layers_G(k)
90 ENDDO
91 DO iLa=2,layers_maxNum
92 layers_num(iLa) = 0
93 layers_name(iLa) = ' '
94 layers_krho(iLa) = 1
95 layers_bolus(iLa) = .TRUE.
96 DO k=1,Nlayers+1
97 layers_bounds(k,iLa) = UNSET_RL
98 ENDDO
99 ENDDO
100 ENDIF
101
102 C-- ensure layers_name/layers_num setup consistency
103 DO iLa=1,layers_maxNum
104 IF ( ( layers_name(iLa).EQ.'TH' ).OR.
105 & ( layers_num(iLa).EQ.1 ) ) THEN
106 layers_name(iLa)='TH'
107 layers_num(iLa)=1
108 ELSEIF ( ( layers_name(iLa).EQ.'SLT' ).OR.
109 & ( layers_num(iLa).EQ.2 ) ) THEN
110 layers_name(iLa)='SLT'
111 layers_num(iLa)=2
112 ELSEIF ( ( layers_name(iLa).EQ.'RHO' ).OR.
113 & ( layers_num(iLa).EQ.3 ) ) THEN
114 layers_name(iLa)='RHO'
115 layers_num(iLa)=3
116 ELSE
117 layers_name(iLa)=' '
118 layers_num(iLa)=0
119 ENDIF
120 ENDDO
121
122 C-- Make sure the layers_bounds we just read is big enough
123 DO iLa=1,layers_maxNum
124 IF ( layers_num(iLa).NE.0 ) THEN
125 DO k=1,Nlayers+1
126 IF ( layers_bounds(k,iLa) .EQ. UNSET_RL ) THEN
127 WRITE(msgBuf,'(2A,I4)')
128 & 'S/R LAYERS_READPARMS: ',
129 & 'No value for layers_bounds at k =', k
130 CALL PRINT_ERROR( msgBuf, myThid )
131 STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
132 ELSE IF ( k .EQ. 1 ) THEN
133 C Do nothing
134 ELSE IF ( layers_bounds(k,iLa) .LE.
135 & layers_bounds(k-1,iLa) ) THEN
136 C Check to make sure layers_bounds is increasing
137 WRITE(msgBuf,'(2A,I4)')
138 & 'S/R LAYERS_READPARMS: ',
139 & 'layers_bounds is not increasing at k =', k
140 CALL PRINT_ERROR( msgBuf, myThid )
141 STOP 'ABNORMAL END: S/R LAYERS_READPARMS'
142 ENDIF
143 ENDDO
144 ENDIF
145 ENDDO
146
147 C-- Make sure that we locally honor the global MNC on/off flag
148 layers_MNC = layers_MNC .AND. useMNC
149 #ifndef ALLOW_MNC
150 C Fix to avoid running without getting any output:
151 layers_MNC = .FALSE.
152 #endif
153 layers_MDSIO = (.NOT. layers_MNC) .OR. outputTypesInclusive
154
155 _END_MASTER(myThid)
156
157 C-- Everyone else must wait for the parameters to be loaded
158 _BARRIER
159
160 #endif /* ALLOW_MYPACKAGE */
161
162 RETURN
163 END

  ViewVC Help
Powered by ViewVC 1.1.22