/[MITgcm]/MITgcm/model/src/ini_masks_etc.F
ViewVC logotype

Annotation of /MITgcm/model/src/ini_masks_etc.F

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


Revision 1.14 - (hide annotations) (download)
Thu Dec 10 00:16:16 1998 UTC (25 years, 5 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint19
Changes since 1.13: +1 -5 lines
Removed some silly diagnostics left-over from the early days.
(print *,'AAAA',...)

1 adcroft 1.14 C $Header: /u/gcmpack/models/MITgcmUV/model/src/ini_masks_etc.F,v 1.13 1998/12/09 16:11:52 adcroft Exp $
2 adcroft 1.1
3 cnh 1.11 #include "CPP_OPTIONS.h"
4 adcroft 1.1
5     CStartOfInterface
6     SUBROUTINE INI_MASKS_ETC( myThid )
7     C /==========================================================\
8     C | SUBROUTINE INI_MASKS_ETC |
9     C | o Initialise masks and topography factors |
10     C |==========================================================|
11     C | These arrays are used throughout the code and describe |
12     C | the topography of the domain through masks (0s and 1s) |
13     C | and fractional height factors (0<hFac<1). The latter |
14     C | distinguish between the lopped-cell and full-step |
15     C | topographic representations. |
16     C \==========================================================/
17 adcroft 1.13 IMPLICIT NONE
18 adcroft 1.1
19     C === Global variables ===
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22     #include "PARAMS.h"
23     #include "GRID.h"
24    
25     C == Routine arguments ==
26 cnh 1.6 C myThid - Number of this instance of INI_MASKS_ETC
27 adcroft 1.1 INTEGER myThid
28     CEndOfInterface
29    
30     C == Local variables ==
31     C bi,bj - Loop counters
32     C I,J,K
33     INTEGER bi, bj
34     INTEGER I, J, K
35    
36     C Calculate quantities derived from XY depth map
37     DO bj = myByLo(myThid), myByHi(myThid)
38     DO bi = myBxLo(myThid), myBxHi(myThid)
39     DO J=1,sNy
40     DO I=1,sNx
41     C Inverse of depth
42     IF ( h(i,j,bi,bj) .EQ. 0. _d 0 ) THEN
43 cnh 1.4 recip_H(i,j,bi,bj) = 0. _d 0
44 adcroft 1.1 ELSE
45 cnh 1.4 recip_H(i,j,bi,bj) = 1. _d 0 / abs( H(i,j,bi,bj) )
46 adcroft 1.1 ENDIF
47 cnh 1.7 depthInK(i,j,bi,bj) = 0.
48 adcroft 1.1 ENDDO
49     ENDDO
50     ENDDO
51     ENDDO
52 cnh 1.4 _EXCH_XY_R4( recip_H, myThid )
53 adcroft 1.2
54     C Calculate lopping factor hFacC
55     DO bj=myByLo(myThid), myByHi(myThid)
56     DO bi=myBxLo(myThid), myBxHi(myThid)
57 cnh 1.4 DO K=1, Nr
58 adcroft 1.2 DO J=1,sNy
59     DO I=1,sNx
60 cnh 1.7 C Round depths within a small fraction of layer depth to that
61     C layer depth.
62 cnh 1.9 IF ( ABS(H(I,J,bi,bj)-rF(K)) .LT.
63     & 1. _d -6*ABS(rF(K)) .AND.
64     & ABS(H(I,J,bi,bj)-rF(K)) .LT.
65     & 1. _d -6*ABS(H(I,J,bi,bj)) )THEN
66 cnh 1.7 H(I,J,bi,bj) = rF(K)
67     ENDIF
68 cnh 1.6 IF ( H(I,J,bi,bj)*rkFac .GE. rF(K)*rkFac ) THEN
69 adcroft 1.3 C Top of cell is below base of domain
70 adcroft 1.2 hFacC(I,J,K,bi,bj) = 0.
71 cnh 1.6 ELSEIF ( H(I,J,bi,bj)*rkFac .LE. rF(K+1)*rkFac ) THEN
72 adcroft 1.3 C Base of domain is below bottom of this cell
73 adcroft 1.2 hFacC(I,J,K,bi,bj) = 1.
74     ELSE
75     C Base of domain is in this cell
76 adcroft 1.3 C Set hFac to the fraction of the cell that is open.
77 adcroft 1.12 hFacC(I,J,K,bi,bj) = (rF(K)*rkFac-H(I,J,bi,bj)*rkFac)*recip_drF(K)
78 adcroft 1.3 ENDIF
79     C Impose minimum fraction
80     IF (hFacC(I,J,K,bi,bj).LT.hFacMin) THEN
81     IF (hFacC(I,J,K,bi,bj).LT.hFacMin*0.5) THEN
82     hFacC(I,J,K,bi,bj)=0.
83     ELSE
84     hFacC(I,J,K,bi,bj)=hFacMin
85     ENDIF
86     ENDIF
87     C Impose minimum size (dimensional)
88 cnh 1.5 IF (drF(k)*hFacC(I,J,K,bi,bj).LT.hFacMinDr) THEN
89     IF (drF(k)*hFacC(I,J,K,bi,bj).LT.hFacMinDr*0.5) THEN
90 adcroft 1.3 hFacC(I,J,K,bi,bj)=0.
91     ELSE
92 cnh 1.5 hFacC(I,J,K,bi,bj)=hFacMinDr*recip_drF(k)
93 adcroft 1.3 ENDIF
94 adcroft 1.2 ENDIF
95 cnh 1.9 depthInK(i,j,bi,bj) = depthInK(i,j,bi,bj)
96     & +hFacC(i,j,k,bi,bj)
97 adcroft 1.2 ENDDO
98     ENDDO
99     ENDDO
100     ENDDO
101     ENDDO
102     _EXCH_XYZ_R4(hFacC , myThid )
103 cnh 1.7 _EXCH_XY_R4( depthInK, myThid )
104    
105 cnh 1.9 CALL PLOT_FIELD_XYRS( depthInK,
106     & 'Model Depths K Index' , 1, myThid )
107 adcroft 1.1
108     C hFacW and hFacS (at U and V points)
109     DO bj=myByLo(myThid), myByHi(myThid)
110     DO bi=myBxLo(myThid), myBxHi(myThid)
111 cnh 1.4 DO K=1, Nr
112 adcroft 1.1 DO J=1,sNy
113     DO I=1,sNx
114     hFacW(I,J,K,bi,bj)=
115     & MIN(hFacC(I,J,K,bi,bj),hFacC(I-1,J,K,bi,bj))
116     hFacS(I,J,K,bi,bj)=
117     & MIN(hFacC(I,J,K,bi,bj),hFacC(I,J-1,K,bi,bj))
118     ENDDO
119     ENDDO
120     ENDDO
121     ENDDO
122     ENDDO
123     _EXCH_XYZ_R4(hFacW , myThid )
124     _EXCH_XYZ_R4(hFacS , myThid )
125    
126     C Masks and reciprocals of hFac[CWS]
127     DO bj = myByLo(myThid), myByHi(myThid)
128     DO bi = myBxLo(myThid), myBxHi(myThid)
129 cnh 1.4 DO K=1,Nr
130 adcroft 1.1 DO J=1,sNy
131     DO I=1,sNx
132 cnh 1.10 IF (HFacC(I,J,K,bi,bj) .NE. 0. _d 0 ) THEN
133     recip_HFacC(I,J,K,bi,bj) = 1. _d 0 / HFacC(I,J,K,bi,bj)
134 adcroft 1.1 ELSE
135 cnh 1.10 recip_HFacC(I,J,K,bi,bj) = 0. _d 0
136 adcroft 1.1 ENDIF
137 cnh 1.10 IF (HFacW(I,J,K,bi,bj) .NE. 0. _d 0 ) THEN
138     recip_HFacW(I,J,K,bi,bj) = 1. _d 0 / HFacW(I,J,K,bi,bj)
139     maskW(I,J,K,bi,bj) = 1. _d 0
140 adcroft 1.1 ELSE
141 cnh 1.10 recip_HFacW(I,J,K,bi,bj) = 0. _d 0
142     maskW(I,J,K,bi,bj) = 0.0 _d 0
143 adcroft 1.1 ENDIF
144 cnh 1.10 IF (HFacS(I,J,K,bi,bj) .NE. 0. _d 0 ) THEN
145     recip_HFacS(I,J,K,bi,bj) = 1. _d 0 / HFacS(I,J,K,bi,bj)
146     maskS(I,J,K,bi,bj) = 1. _d 0
147 adcroft 1.1 ELSE
148 cnh 1.10 recip_HFacS(I,J,K,bi,bj) = 0. _d 0
149     maskS(I,J,K,bi,bj) = 0. _d 0
150 adcroft 1.1 ENDIF
151     ENDDO
152     ENDDO
153     ENDDO
154     ENDDO
155     ENDDO
156 cnh 1.4 _EXCH_XYZ_R4(recip_HFacC , myThid )
157     _EXCH_XYZ_R4(recip_HFacW , myThid )
158     _EXCH_XYZ_R4(recip_HFacS , myThid )
159 adcroft 1.1 _EXCH_XYZ_R4(maskW , myThid )
160     _EXCH_XYZ_R4(maskS , myThid )
161    
162     C Calculate recipricols grid lengths
163     DO bj = myByLo(myThid), myByHi(myThid)
164     DO bi = myBxLo(myThid), myBxHi(myThid)
165     DO J=1,sNy
166     DO I=1,sNx
167 cnh 1.4 recip_dxG(I,J,bi,bj)=1.d0/dxG(I,J,bi,bj)
168     recip_dyG(I,J,bi,bj)=1.d0/dyG(I,J,bi,bj)
169     recip_dxC(I,J,bi,bj)=1.d0/dxC(I,J,bi,bj)
170     recip_dyC(I,J,bi,bj)=1.d0/dyC(I,J,bi,bj)
171     recip_dxF(I,J,bi,bj)=1.d0/dxF(I,J,bi,bj)
172     recip_dyF(I,J,bi,bj)=1.d0/dyF(I,J,bi,bj)
173     recip_dxV(I,J,bi,bj)=1.d0/dxV(I,J,bi,bj)
174     recip_dyU(I,J,bi,bj)=1.d0/dyU(I,J,bi,bj)
175 adcroft 1.1 ENDDO
176     ENDDO
177     ENDDO
178     ENDDO
179 cnh 1.4 _EXCH_XY_R4(recip_dxG, myThid )
180     _EXCH_XY_R4(recip_dyG, myThid )
181     _EXCH_XY_R4(recip_dxC, myThid )
182     _EXCH_XY_R4(recip_dyC, myThid )
183     _EXCH_XY_R4(recip_dxF, myThid )
184     _EXCH_XY_R4(recip_dyF, myThid )
185     _EXCH_XY_R4(recip_dxV, myThid )
186     _EXCH_XY_R4(recip_dyU, myThid )
187 adcroft 1.1
188     C
189     RETURN
190     END

  ViewVC Help
Powered by ViewVC 1.1.22