/[MITgcm]/MITgcm/pkg/rbcs/rbcs_init_fixed.F
ViewVC logotype

Contents of /MITgcm/pkg/rbcs/rbcs_init_fixed.F

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


Revision 1.8 - (show annotations) (download)
Tue Dec 31 22:28:39 2013 UTC (10 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64s, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint65, checkpoint65p, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.7: +9 -15 lines
write relaxation Masks to binary file (when debuglevel >=3); this replace
 calls to PLOT_FIELD_XYRS (less obvious to check).

1 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_init_fixed.F,v 1.7 2011/06/07 22:25:10 jmc Exp $
2 C $Name: $
3
4 #include "RBCS_OPTIONS.h"
5
6 C !INTERFACE: ==========================================================
7 SUBROUTINE RBCS_INIT_FIXED( myThid )
8
9 C !DESCRIPTION:
10 C calls subroutines that initializes fixed variables for relaxed
11 c boundary conditions
12
13 C !USES: ===============================================================
14 IMPLICIT NONE
15 #include "SIZE.h"
16 #include "EEPARAMS.h"
17 #include "PARAMS.h"
18 #include "GRID.h"
19 #ifdef ALLOW_PTRACERS
20 #include "PTRACERS_SIZE.h"
21 #endif
22 #include "RBCS_SIZE.h"
23 #include "RBCS_PARAMS.h"
24 #include "RBCS_FIELDS.h"
25
26 C !INPUT PARAMETERS: ===================================================
27 C myThid :: my Thread Id number
28 INTEGER myThid
29 CEOP
30
31 #ifdef ALLOW_RBCS
32 C !LOCAL VARIABLES:
33 C i,j,k,bi,bj,irbc :: loop indices
34 C msgBuf :: Informational/error message buffer
35 INTEGER i,j,k,bi,bj
36 INTEGER irbc
37 #ifndef DISABLE_RBCS_MOM
38 CHARACTER*(MAX_LEN_MBUF) msgBuf
39 #endif
40 CHARACTER*(12) filName
41
42 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
43
44 #ifndef DISABLE_RBCS_MOM
45 C Loop over tiles
46 DO bj = myByLo(myThid), myByHi(myThid)
47 DO bi = myBxLo(myThid), myBxHi(myThid)
48 DO k=1,Nr
49 DO j=1-Oly,sNy+OLy
50 DO i=1-Olx,sNx+Olx
51 RBC_maskU(i,j,k,bi,bj) = 0. _d 0
52 RBC_maskV(i,j,k,bi,bj) = 0. _d 0
53 ENDDO
54 ENDDO
55 ENDDO
56 ENDDO
57 ENDDO
58 #endif /* DISABLE_RBCS_MOM */
59
60 C Loop over mask index
61 DO irbc=1,maskLEN
62
63 C Loop over tiles
64 DO bj = myByLo(myThid), myByHi(myThid)
65 DO bi = myBxLo(myThid), myBxHi(myThid)
66
67 C Initialize arrays in common blocks :
68 DO k=1,Nr
69 DO j=1-Oly,sNy+OLy
70 DO i=1-Olx,sNx+Olx
71 RBC_mask(i,j,k,bi,bj,irbc) = 0. _d 0
72 ENDDO
73 ENDDO
74 ENDDO
75
76 C end bi,bj loops
77 ENDDO
78 ENDDO
79 C end of mask index loop
80 ENDDO
81
82 C read in mask for relaxing
83 DO irbc=1,maskLEN
84 IF ( relaxMaskFile(irbc).NE. ' ' ) THEN
85 CALL READ_FLD_XYZ_RS(relaxMaskFile(irbc),' ',
86 & RBC_mask(1-Olx,1-Oly,1,1,1,irbc), 0, myThid)
87 CALL EXCH_XYZ_RS( RBC_mask(1-Olx,1-Oly,1,1,1,irbc), myThid )
88 C-- Apply mask:
89 DO bj = myByLo(myThid), myByHi(myThid)
90 DO bi = myBxLo(myThid), myBxHi(myThid)
91 DO k=1,Nr
92 DO j=1-Oly,sNy+OLy
93 DO i=1-Olx,sNx+Olx
94 RBC_mask(i,j,k,bi,bj,irbc) = RBC_mask(i,j,k,bi,bj,irbc)
95 & * maskC(i,j,k,bi,bj)
96 ENDDO
97 ENDDO
98 ENDDO
99 ENDDO
100 ENDDO
101 IF ( debugLevel.GE.debLevC ) THEN
102 WRITE(filName,'(A,I3.3)') 'RBC_mask_',irbc
103 CALL WRITE_FLD_XYZ_RS( filName,' ',
104 & RBC_mask(1-Olx,1-Oly,1,1,1,irbc), 0, myThid )
105 ENDIF
106 ENDIF
107 ENDDO
108
109 #ifndef DISABLE_RBCS_MOM
110 IF ( useRBCuVel .AND. relaxMaskUFile.NE. ' ' ) THEN
111 CALL READ_FLD_XYZ_RS(relaxMaskUFile,' ',RBC_maskU, 0, myThid)
112 ELSEIF( useRBCuVel ) THEN
113 WRITE(msgBuf,'(2A)') '** WARNING ** RBCS_INIT_FIXED: ',
114 & 'no relaxMaskUFile => use Temp mask instead'
115 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
116 & SQUEEZE_RIGHT, myThid )
117 DO bj = myByLo(myThid), myByHi(myThid)
118 DO bi = myBxLo(myThid), myBxHi(myThid)
119 DO k=1,Nr
120 DO j=1-Oly,sNy+OLy
121 DO i=2-Olx,sNx+Olx
122 RBC_maskU(i,j,k,bi,bj) =
123 & ( RBC_mask(i-1,j,k,bi,bj,1)
124 & + RBC_mask( i ,j,k,bi,bj,1) )*0.5 _d 0
125 ENDDO
126 ENDDO
127 ENDDO
128 ENDDO
129 ENDDO
130 ENDIF
131 IF ( useRBCvVel .AND. relaxMaskVFile.NE. ' ' ) THEN
132 CALL READ_FLD_XYZ_RS(relaxMaskVFile,' ',RBC_maskV, 0, myThid)
133 ELSEIF( useRBCvVel ) THEN
134 WRITE(msgBuf,'(2A)') '** WARNING ** RBCS_INIT_FIXED: ',
135 & 'no relaxMaskVFile => use Temp mask instead'
136 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
137 & SQUEEZE_RIGHT, myThid )
138 DO bj = myByLo(myThid), myByHi(myThid)
139 DO bi = myBxLo(myThid), myBxHi(myThid)
140 DO k=1,Nr
141 DO j=2-Oly,sNy+OLy
142 DO i=1-Olx,sNx+Olx
143 RBC_maskV(i,j,k,bi,bj) =
144 & ( RBC_mask(i,j-1,k,bi,bj,1)
145 & + RBC_mask(i, j ,k,bi,bj,1) )*0.5 _d 0
146 ENDDO
147 ENDDO
148 ENDDO
149 ENDDO
150 ENDDO
151 ENDIF
152 IF( useRBCuVel .OR. useRBCvVel ) THEN
153 CALL EXCH_UV_XYZ_RS( RBC_maskU, RBC_maskV, .FALSE., myThid )
154 C-- Apply mask:
155 DO bj = myByLo(myThid), myByHi(myThid)
156 DO bi = myBxLo(myThid), myBxHi(myThid)
157 DO k=1,Nr
158 DO j=1-Oly,sNy+OLy
159 DO i=1-Olx,sNx+Olx
160 RBC_maskU(i,j,k,bi,bj) = RBC_maskU(i,j,k,bi,bj)
161 & * maskW(i,j,k,bi,bj)
162 RBC_maskV(i,j,k,bi,bj) = RBC_maskV(i,j,k,bi,bj)
163 & * maskS(i,j,k,bi,bj)
164 ENDDO
165 ENDDO
166 ENDDO
167 ENDDO
168 ENDDO
169 IF ( debugLevel.GE.debLevC ) THEN
170 CALL WRITE_FLD_XYZ_RS('RBC_maskU',' ',RBC_maskU,0,myThid )
171 CALL WRITE_FLD_XYZ_RS('RBC_maskV',' ',RBC_maskV,0,myThid )
172 ENDIF
173 ENDIF
174 #endif /* DISABLE_RBCS_MOM */
175
176 #endif /* ALLOW_RBCS */
177
178 RETURN
179 END

  ViewVC Help
Powered by ViewVC 1.1.22