/[MITgcm]/MITgcm_contrib/rpa_layers/layers/layers_init_fixed.F
ViewVC logotype

Contents of /MITgcm_contrib/rpa_layers/layers/layers_init_fixed.F

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


Revision 1.2 - (show annotations) (download)
Wed Sep 16 18:04:49 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +8 -5 lines
add CVS header and name.

1 C $Header: $
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 :: fine grid loop index
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 meesage buffer
34 INTEGER k,kk
35 _RL Zf(Nr+1)
36 _RL Zc(Nr)
37 _RL ZZf(FineGridMax+1)
38 _RL ZZc(FineGridMax)
39
40 CHARACTER*(MAX_LEN_MBUF) msgBuf
41
42 #ifdef ALLOW_MNC
43 #ifdef LAYERS_MNC
44 IF (layers_MNC) THEN
45 CALL LAYERS_MNC_INIT( myThid )
46 ENDIF
47 #endif /* LAYERS_MNC */
48 #endif /* ALLOW_MNC */
49
50 C Set up the vertical grid
51
52 C for now, just use up the entire available array for ZZ
53 NZZ = FineGridMax
54
55 C Z and ZZ are INCREASING DOWNWARD!!!
56 C Maybe this is dumb but it will work as long as we are consistent
57
58 C find the depths
59 Zf(1) = 0. _d 0
60 Zc(1) = drC(1)
61 DO k=2,Nr
62 Zf(k) = Zf(k-1) + drF(k-1)
63 Zc(k) = Zc(k-1) + drC(k)
64 ENDDO
65 Zf(Nr+1) = Zf(Nr) + drF(Nr)
66
67
68 C calculate dZZ based on depth
69 dZZ = Zf(Nr+1) / NZZ
70
71
72 C create ZZ
73 ZZf(1) = 0. _d 0
74 ZZc(1) = 0.5 _d 0 * dZZ
75
76 DO kk=2,NZZ
77 ZZf(kk) = ZZf(kk-1) + dZZ
78 ZZc(kk) = ZZc(kk-1) + dZZ
79 ENDDO
80 ZZf(NZZ+1) = ZZf(NZZ) + dZZ
81
82 C create the interpolating mapping arrays
83 k = 1
84 DO kk=1,NZZ
85 C see if ZZc point is less than the top Zc point
86 IF ( ZZc(kk) .LT. Zc(1) ) THEN
87 MapIndex(kk) = 1
88 MapFact(kk) = 1.0 _d 0
89 C see if ZZc point is greater than the bottom Zc point
90 ELSE IF ( (ZZc(kk) .GE. Zc(Nr)) .OR. (k .EQ. Nr) ) THEN
91 MapIndex(kk) = Nr - 1
92 MapFact(kk) = 0.0 _d 0
93 C Otherwise we are somewhere in between and need to do interpolation)
94 ELSE IF ( (ZZc(kk) .GE. Zc(k))
95 & .AND. (ZZc(kk) .LT. Zc(Nr)) ) THEN
96 C Find the proper k value
97 DO WHILE (ZZc(kk) .GE. Zc(k+1))
98 k = k + 1
99 ENDDO
100 C If the loop stopped, that means Zc(k) <= ZZc(kk) < ZZc(k+1)
101 MapIndex(kk) = k
102 MapFact(kk) = 1.0 - (( ZZc(kk) - Zc(k) ) / drC(k+1))
103 ELSE
104 C This means there was a problem
105 WRITE(msgBuf,'(A,I4,A,I4,A,1E14.6,A,2E14.6)')
106 & 'S/R LAYERS_INIT_FIXED: kk=', kk, ' k=', k,
107 & 'ZZc(kk)=', ZZc(kk),' , Zc(k)=',Zc(k)
108 CALL PRINT_ERROR( msgBuf, myThid )
109 STOP 'ABNORMAL END: S/R LAYERS_INIT_FIXED'
110 END IF
111
112 C See which grid box the point lies in
113 IF (ZZc(kk) < Zf(MapIndex(kk)+1)) THEN
114 CellIndex(kk) = MapIndex(kk)
115 ELSE
116 CellIndex(kk) = MapIndex(kk)+1
117 END IF
118 ENDDO
119
120 IF (debugLevel .GT. 0) THEN
121 CALL PRINT_MESSAGE( 'LAYERS_INIT_FIXED Debugging:',
122 & standardMessageUnit,SQUEEZE_RIGHT , 1)
123 DO kk=1,NZZ
124 WRITE(msgBuf,'(A,1F6.1,A,I3,A,I3,A,I3,A,1F6.4)')
125 & '// ZZc=', ZZc(kk),
126 & ', MapIndex(',kk,')=',MapIndex(kk),
127 & ', MapFact(',kk,')=',MapFact(kk)
128 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
129 & SQUEEZE_RIGHT , 1)
130 ENDDO
131 END IF
132
133 RETURN
134 END
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154

  ViewVC Help
Powered by ViewVC 1.1.22