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

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

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


Revision 1.12 - (show annotations) (download)
Tue Jun 16 21:43:10 2015 UTC (8 years, 11 months ago) by rpa
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65n, checkpoint65o, HEAD
Changes since 1.11: +3 -3 lines
fixed a few bugs

1 C $Header: /u/gcmpack/MITgcm/pkg/layers/layers_init_fixed.F,v 1.11 2015/06/03 13:39:22 rpa Exp $
2 C $Name: $
3
4 #include "LAYERS_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 SUBROUTINE LAYERS_INIT_FIXED( myThid )
9
10 C ===================================================================
11 C Initialize LAYERS variables that are kept fixed during the run.
12 C ===================================================================
13
14 IMPLICIT NONE
15 #include "EEPARAMS.h"
16 #include "SIZE.h"
17 #include "PARAMS.h"
18 #include "GRID.h"
19 #include "LAYERS_SIZE.h"
20 #include "LAYERS.h"
21
22 C INPUT/OUTPUT PARAMETERS:
23 C myThid :: my Thread Id number
24 INTEGER myThid
25
26 C LOCAL VARIABLES:
27 C k :: loop index
28 C kk,kkinit :: fine grid loop indices
29 C Zf :: depth at cell boundaries
30 C Zf :: depth at cell centers
31 C ZZf :: depth at cell boundaries (fine grid)
32 C ZZc :: depth at cell centers (fine grid)
33 C msgBuf :: Informational/error message buffer
34 INTEGER k,kk,kkinit,iLa
35 _RL Zf(Nr+1)
36 _RL Zc(Nr)
37 _RL ZZf(FineGridMax+1)
38 _RL ZZc(FineGridMax)
39
40 CHARACTER*11 tmpName
41 CHARACTER*(MAX_LEN_MBUF) msgBuf
42
43 C Functions ::
44 INTEGER ILNBLNK
45 EXTERNAL ILNBLNK
46
47 #ifdef ALLOW_MNC
48 #ifdef LAYERS_MNC
49 IF (layers_MNC) THEN
50 CALL LAYERS_MNC_INIT( myThid )
51 ENDIF
52 #endif /* LAYERS_MNC */
53 #endif /* ALLOW_MNC */
54
55 C Set up the vertical grid
56
57 C for now, just use up the entire available array for ZZ
58 NZZ = FineGridMax
59
60 C Z and ZZ are INCREASING DOWNWARD!!!
61 C Maybe this is dumb but it will work as long as we are consistent
62
63
64 C Each dF cell is split into FineGridFact fine cells
65 C Calculate dZZf on the fine grid
66 kkinit = 1
67 DO k=1,Nr
68 DO kk=kkinit,kkinit+FineGridFact-1
69 dZZf(kk) = dRf(k) / FineGridFact
70 ENDDO
71 kkinit = kkinit + FineGridFact
72 ENDDO
73
74 C find the depths
75 Zf(1) = 0. _d 0
76 Zc(1) = drC(1)
77 DO k=2,Nr
78 Zf(k) = Zf(k-1) + drF(k-1)
79 Zc(k) = Zc(k-1) + drC(k)
80 ENDDO
81 Zf(Nr+1) = Zf(Nr) + drF(Nr)
82
83 C create ZZ
84 ZZf(1) = 0. _d 0
85 ZZc(1) = 0.5 _d 0 * dZZf(1)
86
87 DO kk=2,NZZ+1
88 ZZf(kk) = ZZf(kk-1) + dZZf(kk-1)
89 ZZc(kk-1) = 0.5 _d 0 * (ZZf(kk) + ZZf(kk-1))
90 ENDDO
91
92 C create the interpolating mapping arrays
93 k = 1
94 DO kk=1,NZZ
95 C see if ZZc point is less than the top Zc point
96 IF ( ZZc(kk) .LT. Zc(1) ) THEN
97 MapIndex(kk) = 1
98 MapFact(kk) = 1.0 _d 0
99 C see if ZZc point is greater than the bottom Zc point
100 ELSE IF ( (ZZc(kk) .GE. Zc(Nr)) .OR. (k .EQ. Nr) ) THEN
101 MapIndex(kk) = Nr - 1
102 MapFact(kk) = 0.0 _d 0
103 C Otherwise we are somewhere in between and need to do interpolation)
104 ELSE IF ( (ZZc(kk) .GE. Zc(k))
105 & .AND. (ZZc(kk) .LT. Zc(Nr)) ) THEN
106 C Find the proper k value
107 DO WHILE (ZZc(kk) .GE. Zc(k+1))
108 k = k + 1
109 ENDDO
110 C If the loop stopped, that means Zc(k) <= ZZc(kk) < ZZc(k+1)
111 MapIndex(kk) = k
112 MapFact(kk) = 1.0 - (( ZZc(kk) - Zc(k) ) / drC(k+1))
113 ELSE
114 C This means there was a problem
115 WRITE(msgBuf,'(A,I4,A,I4,A,1E14.6,A,2E14.6)')
116 & 'S/R LAYERS_INIT_FIXED: kk=', kk, ', k=', k,
117 & ', ZZc(kk)=', ZZc(kk),' , Zc(k)=',Zc(k)
118 CALL PRINT_ERROR( msgBuf, myThid )
119 STOP 'ABNORMAL END: S/R LAYERS_INIT_FIXED'
120 ENDIF
121
122 C See which grid box the point lies in
123 IF ( ZZc(kk).LT.Zf(MapIndex(kk)+1) ) THEN
124 CellIndex(kk) = MapIndex(kk)
125 ELSE
126 CellIndex(kk) = MapIndex(kk)+1
127 ENDIF
128 ENDDO
129
130 IF ( debugLevel .GE. debLevB ) THEN
131 CALL PRINT_MESSAGE( 'LAYERS_INIT_FIXED Debugging:',
132 & standardMessageUnit, SQUEEZE_RIGHT, myThid )
133 DO kk=1,NZZ
134 WRITE(msgBuf,'(A,1F6.1,A,I3,A,I3,A,I3,A,1F6.4,A,I3,A,I3)')
135 & '// ZZc=', ZZc(kk),
136 & ', MapIndex(',kk,')=',MapIndex(kk),
137 & ', MapFact(',kk,')=',MapFact(kk),
138 & ', CellIndex(',kk,')=',CellIndex(kk)
139 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
140 & SQUEEZE_RIGHT, myThid )
141 ENDDO
142 ENDIF
143
144 C Output the layer coordinates
145 DO iLa=1,layers_maxNum
146 IF ( layers_num(iLa).NE.0 ) THEN
147 WRITE(tmpName,'(A7,I1,A3)') 'layers',iLa,layers_name(iLa)
148 CALL WRITE_GLVEC_RL( tmpName, ' ',layers_bounds(1,iLa),1+Nlayers,
149 & -1, myThid )
150 ENDIF
151 ENDDO
152
153 C --- Set up layers "w-grid" for transformation calculation
154 #ifdef LAYERS_THERMODYNAMICS
155 DO iLa=1,layers_maxNum
156 IF ( layers_num(iLa).NE.0 ) THEN
157 DO k=1,Nlayers
158 layers_bounds_w(k,iLa) = 0.5 _d 0 * (
159 & layers_bounds(k+1,iLa) +
160 & layers_bounds(k,iLa) )
161 ENDDO
162 DO k=1,Nlayers-1
163 layers_recip_delta(k,iLa) = 1.0 _d 0 / (
164 & layers_bounds_w(k+1,iLa) -
165 & layers_bounds_w(k,iLa) )
166 ENDDO
167 ENDIF
168 ENDDO
169 #endif /* LAYERS_THERMODYNAMICS */
170
171 #ifdef ALLOW_DIAGNOSTICS
172 IF ( useDiagnostics ) THEN
173 CALL LAYERS_DIAGNOSTICS_INIT( myThid )
174 ENDIF
175 #endif
176
177 RETURN
178 END

  ViewVC Help
Powered by ViewVC 1.1.22