/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_som_adv_y.F
ViewVC logotype

Diff of /MITgcm/pkg/generic_advdiff/gad_som_adv_y.F

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

revision 1.1 by jmc, Tue Jan 16 04:38:34 2007 UTC revision 1.5 by jmc, Fri May 9 21:43:16 2008 UTC
# Line 9  C !ROUTINE: GAD_SOM_ADV_Y Line 9  C !ROUTINE: GAD_SOM_ADV_Y
9  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
10        SUBROUTINE GAD_SOM_ADV_Y(        SUBROUTINE GAD_SOM_ADV_Y(
11       I           bi,bj,k, limiter,       I           bi,bj,k, limiter,
12         I           overlapOnly, interiorOnly,
13         I           N_edge, S_edge, E_edge, W_edge,
14       I           deltaTloc, vTrans,       I           deltaTloc, vTrans,
15       U           sm_v, sm_o, sm_x, sm_y, sm_z,       U           sm_v, sm_o, sm_x, sm_y, sm_z,
16       U           sm_xx, sm_yy, sm_zz, sm_xy, sm_xz, sm_yz,       U           sm_xx, sm_yy, sm_zz, sm_xy, sm_xz, sm_yz,
# Line 34  C---+----1----+----2----+----3----+----4 Line 36  C---+----1----+----2----+----3----+----4
36  C !USES: ===============================================================  C !USES: ===============================================================
37        IMPLICIT NONE        IMPLICIT NONE
38  #include "SIZE.h"  #include "SIZE.h"
 c #include "GRID.h"  
39  #include "GAD.h"  #include "GAD.h"
40    
41  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
42  C  bi,bj        :: tile indices  C  bi,bj         :: tile indices
43  C  k            :: vertical level  C  k             :: vertical level
44  C  limiter      :: 0: no limiter ; 1: Prather, 1986 limiter  C  limiter       :: 0: no limiter ; 1: Prather, 1986 limiter
45  C  vTrans       :: zonal volume transport  C  overlapOnly   :: only update the edges of myTile, but not the interior
46  C  myThid       :: my Thread Id. number  C  interiorOnly  :: only update the interior of myTile, but not the edges
47    C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
48    C  vTrans        :: zonal volume transport
49    C  myThid        :: my Thread Id. number
50        INTEGER bi,bj,k        INTEGER bi,bj,k
51        INTEGER limiter        INTEGER limiter
52          LOGICAL overlapOnly, interiorOnly
53          LOGICAL N_edge, S_edge, E_edge, W_edge
54        _RL deltaTloc        _RL deltaTloc
55        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
 c     _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
56        INTEGER myThid        INTEGER myThid
57    
58  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
# Line 70  C  vT           :: meridional advective Line 75  C  vT           :: meridional advective
75        _RL sm_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL sm_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76        _RL vT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77    
 #ifdef GAD_ALLOW_SOM_ADVECT  
78  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
79  C  i,j          :: loop indices  C  i,j           :: loop indices
80  C  vLoc         :: volume transported (per time step)  C  vLoc          :: volume transported (per time step)
81    C [iMin,iMax]Upd :: loop range to update tracer field
82    C [jMin,jMax]Upd :: loop range to update tracer field
83    C  nbStrips      :: number of strips (if region to update is splitted)
84        _RL two, three        _RL two, three
85        PARAMETER( two   = 2. _d 0 )        PARAMETER( two   = 2. _d 0 )
86        PARAMETER( three = 3. _d 0 )        PARAMETER( three = 3. _d 0 )
87        INTEGER i,j        INTEGER i,j
88          INTEGER ns, nbStrips
89          INTEGER iMinUpd(2), iMaxUpd(2), jMinUpd(2), jMaxUpd(2)
90          _RL  recip_dT
91        _RL  slpmax, s1max, s1new, s2new        _RL  slpmax, s1max, s1new, s2new
92        _RL  vLoc, alf1, alf1q, alpmn        _RL  vLoc, alf1, alf1q, alpmn
93        _RL  alfp, alpq, alp1, locTp        _RL  alfp, alpq, alp1, locTp
# Line 108  C  vLoc         :: volume transported (p Line 118  C  vLoc         :: volume transported (p
118        _RL  fn_yz(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  fn_yz(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119  CEOP  CEOP
120    
121          recip_dT = 0.
122          IF ( deltaTloc.GT.0. _d 0 ) recip_dT = 1.0 _d 0 / deltaTloc
123    
124    C-    Set loop ranges for updating tracer field (splitted in 2 strips)
125          nbStrips   = 1
126          iMinUpd(1) = 1-Olx
127          iMaxUpd(1) = sNx+Olx
128          jMinUpd(1) = 1-Oly+1
129          jMaxUpd(1) = sNy+Oly-1
130          IF ( overlapOnly ) THEN
131    C     update in overlap-Only
132            IF ( S_edge ) jMinUpd(1) = 1
133            IF ( N_edge ) jMaxUpd(1) = sNy
134            IF ( W_edge ) THEN
135              iMinUpd(1) = 1-Olx
136              iMaxUpd(1) = 0
137            ENDIF
138            IF ( E_edge ) THEN
139              IF ( W_edge ) nbStrips = 2
140              iMinUpd(nbStrips) = sNx+1
141              iMaxUpd(nbStrips) = sNx+Olx
142            ENDIF
143          ELSE
144    C     do not only update the overlap
145            IF ( interiorOnly .AND. W_edge ) iMinUpd(1) = 1
146            IF ( interiorOnly .AND. E_edge ) iMaxUpd(1) = sNx
147          ENDIF
148    
149    C-    Internal exchange for calculations in Y
150    c     IF ( overlapOnly ) THEN
151    c         CALL GAD_SOM_FILL_CS_CORNER( .FALSE.,
152    c    U           sm_v,  sm_o,  sm_x,  sm_y,  sm_z,
153    c    U           sm_xx, sm_yy, sm_zz, sm_xy, sm_xz, sm_yz,
154    c    I           bi, bj, myThid )
155    c     ENDIF
156    
157    C--   start 1rst loop on strip number "ns"
158          DO ns=1,nbStrips
159    
160        IF ( limiter.EQ.1 ) THEN        IF ( limiter.EQ.1 ) THEN
161         DO j=1-OLy,sNy+OLy         DO j=jMinUpd(1)-1,jMaxUpd(1)+1
162          DO i=1-OLx,sNx+OLx          DO i=iMinUpd(ns),iMaxUpd(ns)
163  C     If flux-limiting transport is to be applied, place limits on  C     If flux-limiting transport is to be applied, place limits on
164  C     appropriate moments before transport.  C     appropriate moments before transport.
165           slpmax = 0.           slpmax = 0.
# Line 121  C     appropriate moments before transpo Line 170  C     appropriate moments before transpo
170       &                MAX(ABS(s1new)-slpmax,sm_yy(i,j))  )       &                MAX(ABS(s1new)-slpmax,sm_yy(i,j))  )
171           sm_xy(i,j) = MIN( slpmax, MAX(-slpmax,sm_xy(i,j)) )           sm_xy(i,j) = MIN( slpmax, MAX(-slpmax,sm_xy(i,j)) )
172           sm_yz(i,j) = MIN( slpmax, MAX(-slpmax,sm_yz(i,j)) )           sm_yz(i,j) = MIN( slpmax, MAX(-slpmax,sm_yz(i,j)) )
173           sm_y (i,j) = s1new ;           sm_y (i,j) = s1new
174           sm_yy(i,j) = s2new ;           sm_yy(i,j) = s2new
175          ENDDO          ENDDO
176         ENDDO         ENDDO
177        ENDIF        ENDIF
178    
179  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
180  C---  part.1 : calculate flux for all moments  C---  part.1 : calculate flux for all moments
181        DO i=1-OLx,sNx+OLx        DO j=jMinUpd(1),jMaxUpd(1)+1
182         vT(i,1-OLy)=0.         DO i=iMinUpd(ns),iMaxUpd(ns)
       ENDDO  
       DO j=1-OLy+1,sNy+OLy  
        DO i=1-OLx,sNx+OLx  
183          vLoc = vTrans(i,j)*deltaTloc          vLoc = vTrans(i,j)*deltaTloc
184  C--    Flux from (j-1) to (j) when V>0 (i.e., take right side of box j-1)  C--    Flux from (j-1) to (j) when V>0 (i.e., take right side of box j-1)
185          fp_v (i,j) = MAX( 0. _d 0,  vLoc )          fp_v (i,j) = MAX( 0. _d 0,  vLoc )
# Line 175  C       use same indexing as velocity, " Line 221  C       use same indexing as velocity, "
221          fn_zz(i,j) = aln(i,j)*sm_zz(i, j )          fn_zz(i,j) = aln(i,j)*sm_zz(i, j )
222          fn_xz(i,j) = aln(i,j)*sm_xz(i, j )          fn_xz(i,j) = aln(i,j)*sm_xz(i, j )
223  C--    Save zero-order flux:  C--    Save zero-order flux:
224          vT(i,j)    = fp_o(i,j) - fn_o(i,j)          vT(i,j) = ( fp_o(i,j) - fn_o(i,j) )*recip_dT
225         ENDDO         ENDDO
226        ENDDO        ENDDO
227    
228    C--   end 1rst loop on strip number "ns"
229    c     ENDDO
230    
231    C-    Internal exchange for next calculations in X
232    c     IF ( overlapOnly ) THEN
233    c         CALL GAD_SOM_FILL_CS_CORNER( .TRUE.,
234    c    U           sm_v,  sm_o,  sm_x,  sm_y,  sm_z,
235    c    U           sm_xx, sm_yy, sm_zz, sm_xy, sm_xz, sm_yz,
236    c    I           bi, bj, myThid )
237    c     ENDIF
238    
239  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
240    C--   start 2nd loop on strip number "ns"
241    c     DO ns=1,nbStrips
242    
243  C---  part.2 : re-adjust moments remaining in the box  C---  part.2 : re-adjust moments remaining in the box
244  C      take off from grid box (j): negative V(j) and positive V(j+1)  C      take off from grid box (j): negative V(j) and positive V(j+1)
245        DO j=1-OLy+1,sNy+OLy-1        DO j=jMinUpd(1),jMaxUpd(1)
246         DO i=1-OLx,sNx+OLx         DO i=iMinUpd(ns),iMaxUpd(ns)
247          alf1  = 1. _d 0 - aln(i,j) - alp(i,j+1)          alf1  = 1. _d 0 - aln(i,j) - alp(i,j+1)
248          alf1q = alf1*alf1          alf1q = alf1*alf1
249          alpmn = alp(i,j+1) - aln(i,j)          alpmn = alp(i,j+1) - aln(i,j)
# Line 204  C      take off from grid box (j): negat Line 264  C      take off from grid box (j): negat
264  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
265  C---  part.3 : Put the temporary moments into appropriate neighboring boxes  C---  part.3 : Put the temporary moments into appropriate neighboring boxes
266  C      add into grid box (j): positive V(j) and negative V(j+1)  C      add into grid box (j): positive V(j) and negative V(j+1)
267        DO j=1-OLy+1,sNy+OLy-1        DO j=jMinUpd(1),jMaxUpd(1)
268         DO i=1-OLx,sNx+OLx         DO i=iMinUpd(ns),iMaxUpd(ns)
269          sm_v (i,j) = sm_v (i,j) + fp_v (i,j) + fn_v (i,j+1)          sm_v (i,j) = sm_v (i,j) + fp_v (i,j) + fn_v (i,j+1)
270          alfp = fp_v(i, j )/sm_v(i,j)          alfp = fp_v(i, j )/sm_v(i,j)
271          alfn = fn_v(i,j+1)/sm_v(i,j)          alfn = fn_v(i,j+1)/sm_v(i,j)
# Line 243  C      add into grid box (j): positive V Line 303  C      add into grid box (j): positive V
303         ENDDO         ENDDO
304        ENDDO        ENDDO
305    
306  #endif /* GAD_ALLOW_SOM_ADVECT */  C--   end 2nd loop on strip number "ns"
307          ENDDO
308    
309        RETURN        RETURN
310        END        END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22