/[MITgcm]/MITgcm/pkg/seaice/seaice_calc_strainrates.F
ViewVC logotype

Diff of /MITgcm/pkg/seaice/seaice_calc_strainrates.F

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

revision 1.17 by mlosch, Fri Nov 5 08:13:03 2010 UTC revision 1.18 by jmc, Fri Oct 21 17:32:01 2011 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "SEAICE_OPTIONS.h"  #include "SEAICE_OPTIONS.h"
5    #ifdef ALLOW_OBCS
6    # include "OBCS_OPTIONS.h"
7    #else
8    # define OBCS_UVICE_OLD
9    #endif
10    
11  CStartOfInterface  CBOP
12    C     !ROUTINE: SEAICE_CALC_STRAINRATES
13    C     !INTERFACE:
14        SUBROUTINE SEAICE_CALC_STRAINRATES(        SUBROUTINE SEAICE_CALC_STRAINRATES(
15       I     uFld, vFld,       I     uFld, vFld,
16       O     e11Loc, e22Loc, e12Loc,       O     e11Loc, e22Loc, e12Loc,
17       I     iStep, myTime, myIter, myThid )       I     iStep, myTime, myIter, myThid )
18  C     /==========================================================\  
19  C     | SUBROUTINE  SEAICE_CALC_STRAINRATES                      |  C     !DESCRIPTION: \bv
20  C     | o compute strain rates from ice velocities               |  C     *==========================================================*
21  C     |==========================================================|  C     | SUBROUTINE  SEAICE_CALC_STRAINRATES
22  C     | written by Martin Losch, Apr 2007                        |  C     | o compute strain rates from ice velocities
23  C     \==========================================================/  C     *==========================================================*
24    C     | written by Martin Losch, Apr 2007
25    C     *==========================================================*
26    C     \ev
27    
28    C     !USES:
29        IMPLICIT NONE        IMPLICIT NONE
30    
31  C     === Global variables ===  C     === Global variables ===
# Line 28  C     === Global variables === Line 40  C     === Global variables ===
40  # include "tamc.h"  # include "tamc.h"
41  #endif  #endif
42    
43    C     !INPUT/OUTPUT PARAMETERS:
44  C     === Routine arguments ===  C     === Routine arguments ===
45    C     uFld   :: ice velocity, u-component
46    C     vFld   :: ice velocity, v-component
47    C     e11Loc :: strain rate tensor, component 1,1
48    C     e22Loc :: strain rate tensor, component 2,2
49    C     e12Loc :: strain rate tensor, component 1,2
50  C     iStep  :: Sub-time-step number  C     iStep  :: Sub-time-step number
51  C     myTime :: Simulation time  C     myTime :: Simulation time
52  C     myIter :: Simulation timestep number  C     myIter :: Simulation timestep number
53  C     myThid :: My Thread Id. number  C     myThid :: My Thread Id. number
       INTEGER iStep  
       _RL     myTime  
       INTEGER myIter  
       INTEGER myThid  
 C     ice velocities  
54        _RL uFld   (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)        _RL uFld   (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
55        _RL vFld   (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)        _RL vFld   (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
 C     strain rate tensor  
56        _RL e11Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RL e11Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
57        _RL e22Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RL e22Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
58        _RL e12Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RL e12Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
59  CEndOfInterface        INTEGER iStep
60          _RL     myTime
61          INTEGER myIter
62          INTEGER myThid
63    CEOP
64    
65  #ifdef SEAICE_CGRID  #ifdef SEAICE_CGRID
66  #ifdef SEAICE_ALLOW_DYNAMICS  #ifdef SEAICE_ALLOW_DYNAMICS
67    C     !LOCAL VARIABLES:
68  C     === Local variables ===  C     === Local variables ===
69  C     i,j,bi,bj - Loop counters  C     i,j,bi,bj :: Loop counters
70        INTEGER i, j, bi, bj        INTEGER i, j, bi, bj
71  C     hFacU, hFacV - determine the no-slip boundary condition  C     hFacU, hFacV :: determine the no-slip boundary condition
72        INTEGER k        INTEGER k
73        _RS hFacU, hFacV, noSlipFac        _RS hFacU, hFacV, noSlipFac
74  C     auxillary variables that help writing code that  C     auxillary variables that help writing code that
# Line 73  C     abbreviations on C-points, need to Line 90  C     abbreviations on C-points, need to
90  C     for vectorization  C     for vectorization
91          DO j=1-Oly,sNy+Oly-1          DO j=1-Oly,sNy+Oly-1
92           DO i=1-Olx,sNx+Olx-1           DO i=1-Olx,sNx+Olx-1
93            dudx(I,J) = _recip_dxF(I,J,bi,bj) *            dudx(i,j) = _recip_dxF(i,j,bi,bj) *
94       &         (uFld(I+1,J,bi,bj)-uFld(I,J,bi,bj))       &         (uFld(i+1,j,bi,bj)-uFld(i,j,bi,bj))
95            uave(I,J) = 0.5 _d 0 * (uFld(I,J,bi,bj)+uFld(I+1,J,bi,bj))            uave(i,j) = 0.5 _d 0 * (uFld(i,j,bi,bj)+uFld(i+1,j,bi,bj))
96           ENDDO           ENDDO
97          ENDDO          ENDDO
98          DO j=1-Oly,sNy+Oly-1          DO j=1-Oly,sNy+Oly-1
99           DO i=1-Olx,sNx+Olx-1           DO i=1-Olx,sNx+Olx-1
100            dvdy(I,J) = _recip_dyF(I,J,bi,bj) *            dvdy(i,j) = _recip_dyF(i,j,bi,bj) *
101       &         (vFld(I,J+1,bi,bj)-vFld(I,J,bi,bj))       &         (vFld(i,j+1,bi,bj)-vFld(i,j,bi,bj))
102            vave(I,J) = 0.5 _d 0 * (vFld(I,J,bi,bj)+vFld(I,J+1,bi,bj))            vave(i,j) = 0.5 _d 0 * (vFld(i,j,bi,bj)+vFld(i,j+1,bi,bj))
103           ENDDO           ENDDO
104          ENDDO          ENDDO
105  C     evaluate strain rates at C-points  C     evaluate strain rates at C-points
106          DO j=1-Oly,sNy+Oly-1          DO j=1-Oly,sNy+Oly-1
107           DO i=1-Olx,sNx+Olx-1           DO i=1-Olx,sNx+Olx-1
108            e11Loc(I,J,bi,bj) = dudx(I,J) + vave(I,J) * k2AtC(I,J,bi,bj)            e11Loc(i,j,bi,bj) = dudx(i,j) + vave(i,j) * k2AtC(i,j,bi,bj)
109            e22Loc(I,J,bi,bj) = dvdy(I,J) + uave(I,J) * k1AtC(I,J,bi,bj)            e22Loc(i,j,bi,bj) = dvdy(i,j) + uave(i,j) * k1AtC(i,j,bi,bj)
110             ENDDO
111            ENDDO
112    #ifndef OBCS_UVICE_OLD
113    C--     for OBCS: assume no gradient beyong OB
114            DO j=1-Oly,sNy+Oly-1
115             DO i=1-Olx,sNx+Olx-1
116              e11Loc(i,j,bi,bj) = e11Loc(i,j,bi,bj)*maskInC(i,j,bi,bj)
117              e22Loc(i,j,bi,bj) = e22Loc(i,j,bi,bj)*maskInC(i,j,bi,bj)
118           ENDDO           ENDDO
119          ENDDO          ENDDO
120    #endif /* OBCS_UVICE_OLD */
121    
122  C     abbreviations at Z-points, need to do them in separate loops  C     abbreviations at Z-points, need to do them in separate loops
123  C     for vectorization  C     for vectorization
124          DO j=1-Oly+1,sNy+Oly          DO j=1-Oly+1,sNy+Oly
125           DO i=1-Olx+1,sNx+Olx           DO i=1-Olx+1,sNx+Olx
126            dudy(I,J) = ( uFld(I,J,bi,bj) - uFld(I  ,J-1,bi,bj) )            dudy(i,j) = ( uFld(i,j,bi,bj) - uFld(i  ,j-1,bi,bj) )
127       &         * _recip_dyU(I,J,bi,bj)       &         * _recip_dyU(i,j,bi,bj)
128            uave(I,J) = 0.5 _d 0 * (uFld(I,J,bi,bj)+uFld(I  ,J-1,bi,bj))            uave(i,j) = 0.5 _d 0 * (uFld(i,j,bi,bj)+uFld(i  ,j-1,bi,bj))
129           ENDDO           ENDDO
130          ENDDO          ENDDO
131          DO j=1-Oly+1,sNy+Oly          DO j=1-Oly+1,sNy+Oly
132           DO i=1-Olx+1,sNx+Olx           DO i=1-Olx+1,sNx+Olx
133            dvdx(I,J) = ( vFld(I,J,bi,bj) - vFld(I-1,J  ,bi,bj) )            dvdx(i,j) = ( vFld(i,j,bi,bj) - vFld(i-1,j  ,bi,bj) )
134       &         * _recip_dxV(I,J,bi,bj)       &         * _recip_dxV(i,j,bi,bj)
135            vave(I,J) = 0.5 _d 0 * (vFld(I,J,bi,bj)+vFld(I-1,J  ,bi,bj))            vave(i,j) = 0.5 _d 0 * (vFld(i,j,bi,bj)+vFld(i-1,j  ,bi,bj))
136           ENDDO           ENDDO
137          ENDDO          ENDDO
138  C     evaluate strain rates at Z-points  C     evaluate strain rates at Z-points
# Line 113  C     evaluate strain rates at Z-points Line 140  C     evaluate strain rates at Z-points
140           DO i=1-Olx+1,sNx+Olx           DO i=1-Olx+1,sNx+Olx
141            hFacU = _maskW(i,j,k,bi,bj) - _maskW(i,j-1,k,bi,bj)            hFacU = _maskW(i,j,k,bi,bj) - _maskW(i,j-1,k,bi,bj)
142            hFacV = _maskS(i,j,k,bi,bj) - _maskS(i-1,j,k,bi,bj)            hFacV = _maskS(i,j,k,bi,bj) - _maskS(i-1,j,k,bi,bj)
143            e12Loc(I,J,bi,bj) = 0.5 _d 0 * (            e12Loc(i,j,bi,bj) = 0.5 _d 0 * (
144       &         dudy(I,J) + dvdx(I,J)       &         dudy(i,j) + dvdx(i,j)
145       &         - k1AtZ(I,J,bi,bj) * vave(I,J)       &         - k1AtZ(i,j,bi,bj) * vave(i,j)
146       &         - k2AtZ(I,J,bi,bj) * uave(I,J)       &         - k2AtZ(i,j,bi,bj) * uave(i,j)
147       &         )       &         )
148       &         *maskC(I  ,J  ,k,bi,bj)*maskC(I-1,J  ,k,bi,bj)       &         *maskC(i  ,j  ,k,bi,bj)*maskC(i-1,j  ,k,bi,bj)
149       &         *maskC(I  ,J-1,k,bi,bj)*maskC(I-1,J-1,k,bi,bj)       &         *maskC(i  ,j-1,k,bi,bj)*maskC(i-1,j-1,k,bi,bj)
150       &         + 2.0 _d 0 * noSlipFac * (       &         + 2.0 _d 0 * noSlipFac * (
151       &           2.0 _d 0 * uave(I,J) * _recip_dyU(I,J,bi,bj) * hFacU       &           2.0 _d 0 * uave(i,j) * _recip_dyU(i,j,bi,bj) * hFacU
152       &         + 2.0 _d 0 * vave(I,J) * _recip_dxV(I,J,bi,bj) * hFacV       &         + 2.0 _d 0 * vave(i,j) * _recip_dxV(i,j,bi,bj) * hFacV
153       &         )       &         )
154  C     no slip at the boundary implies u(j)+u(j-1)=0 and v(i)+v(i-1)=0  C     no slip at the boundary implies u(j)+u(j-1)=0 and v(i)+v(i-1)=0
155  C     accross the boundary; this is already accomplished by masking so  C     accross the boundary; this is already accomplished by masking so
156  C     that the following lines are not necessary  C     that the following lines are not necessary
157  c$$$     &         - hFacV * k1AtZ(I,J,bi,bj) * vave(I,J)  c$$$     &         - hFacV * k1AtZ(i,j,bi,bj) * vave(i,j)
158  c$$$     &         - hFacU * k2AtZ(I,J,bi,bj) * uave(I,J)  c$$$     &         - hFacU * k2AtZ(i,j,bi,bj) * uave(i,j)
159           ENDDO           ENDDO
160          ENDDO          ENDDO
161    

Legend:
Removed from v.1.17  
changed lines
  Added in v.1.18

  ViewVC Help
Powered by ViewVC 1.1.22