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

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

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


Revision 1.18 - (hide annotations) (download)
Fri Oct 21 17:32:01 2011 UTC (12 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g
Changes since 1.17: +68 -41 lines
new implementation of OBCS in seaice-dynamics: prevent SEAICE_LSR or SEAICE_EVP
to modify OB values (consistent with an implicit method).

1 jmc 1.18 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_calc_strainrates.F,v 1.17 2010/11/05 08:13:03 mlosch Exp $
2 mlosch 1.1 C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5 jmc 1.18 #ifdef ALLOW_OBCS
6     # include "OBCS_OPTIONS.h"
7     #else
8     # define OBCS_UVICE_OLD
9     #endif
10 mlosch 1.1
11 jmc 1.18 CBOP
12     C !ROUTINE: SEAICE_CALC_STRAINRATES
13     C !INTERFACE:
14 jmc 1.8 SUBROUTINE SEAICE_CALC_STRAINRATES(
15 mlosch 1.1 I uFld, vFld,
16 mlosch 1.12 O e11Loc, e22Loc, e12Loc,
17 mlosch 1.14 I iStep, myTime, myIter, myThid )
18 jmc 1.18
19     C !DESCRIPTION: \bv
20     C *==========================================================*
21     C | SUBROUTINE SEAICE_CALC_STRAINRATES
22     C | o compute strain rates from ice velocities
23     C *==========================================================*
24     C | written by Martin Losch, Apr 2007
25     C *==========================================================*
26     C \ev
27    
28     C !USES:
29 mlosch 1.1 IMPLICIT NONE
30    
31     C === Global variables ===
32     #include "SIZE.h"
33     #include "EEPARAMS.h"
34     #include "PARAMS.h"
35     #include "GRID.h"
36     #include "SEAICE_PARAMS.h"
37 mlosch 1.11 #include "SEAICE.h"
38 mlosch 1.1
39     #ifdef ALLOW_AUTODIFF_TAMC
40     # include "tamc.h"
41     #endif
42    
43 jmc 1.18 C !INPUT/OUTPUT PARAMETERS:
44 mlosch 1.1 C === Routine arguments ===
45 jmc 1.18 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 jmc 1.8 C iStep :: Sub-time-step number
51     C myTime :: Simulation time
52     C myIter :: Simulation timestep number
53     C myThid :: My Thread Id. number
54 mlosch 1.14 _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)
56 mlosch 1.12 _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)
58     _RL e12Loc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
59 jmc 1.18 INTEGER iStep
60     _RL myTime
61     INTEGER myIter
62     INTEGER myThid
63     CEOP
64 mlosch 1.1
65     #ifdef SEAICE_CGRID
66     #ifdef SEAICE_ALLOW_DYNAMICS
67 jmc 1.18 C !LOCAL VARIABLES:
68 mlosch 1.1 C === Local variables ===
69 jmc 1.18 C i,j,bi,bj :: Loop counters
70 mlosch 1.1 INTEGER i, j, bi, bj
71 jmc 1.18 C hFacU, hFacV :: determine the no-slip boundary condition
72 mlosch 1.2 INTEGER k
73 mlosch 1.11 _RS hFacU, hFacV, noSlipFac
74 mlosch 1.15 C auxillary variables that help writing code that
75     C vectorizes even after TAFization
76     _RL dudx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77     _RL dvdy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78     _RL dudy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79     _RL dvdx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80     _RL uave (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81     _RL vave (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82 mlosch 1.2
83 mlosch 1.4 k = 1
84 mlosch 1.11 noSlipFac = 0. _d 0
85     IF ( SEAICE_no_slip ) noSlipFac = 1. _d 0
86 mlosch 1.1 C
87 mlosch 1.11 DO bj=myByLo(myThid),myByHi(myThid)
88     DO bi=myBxLo(myThid),myBxHi(myThid)
89 mlosch 1.15 C abbreviations on C-points, need to do them in separate loops
90     C for vectorization
91 mlosch 1.11 DO j=1-Oly,sNy+Oly-1
92     DO i=1-Olx,sNx+Olx-1
93 jmc 1.18 dudx(i,j) = _recip_dxF(i,j,bi,bj) *
94     & (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))
96 mlosch 1.15 ENDDO
97     ENDDO
98     DO j=1-Oly,sNy+Oly-1
99     DO i=1-Olx,sNx+Olx-1
100 jmc 1.18 dvdy(i,j) = _recip_dyF(i,j,bi,bj) *
101     & (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))
103 mlosch 1.15 ENDDO
104     ENDDO
105     C evaluate strain rates at C-points
106     DO j=1-Oly,sNy+Oly-1
107     DO i=1-Olx,sNx+Olx-1
108 jmc 1.18 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)
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 mlosch 1.11 ENDDO
119     ENDDO
120 jmc 1.18 #endif /* OBCS_UVICE_OLD */
121    
122 mlosch 1.15 C abbreviations at Z-points, need to do them in separate loops
123     C for vectorization
124     DO j=1-Oly+1,sNy+Oly
125     DO i=1-Olx+1,sNx+Olx
126 jmc 1.18 dudy(i,j) = ( uFld(i,j,bi,bj) - uFld(i ,j-1,bi,bj) )
127     & * _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))
129 mlosch 1.15 ENDDO
130     ENDDO
131     DO j=1-Oly+1,sNy+Oly
132     DO i=1-Olx+1,sNx+Olx
133 jmc 1.18 dvdx(i,j) = ( vFld(i,j,bi,bj) - vFld(i-1,j ,bi,bj) )
134     & * _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))
136 mlosch 1.15 ENDDO
137     ENDDO
138     C evaluate strain rates at Z-points
139 mlosch 1.11 DO j=1-Oly+1,sNy+Oly
140     DO i=1-Olx+1,sNx+Olx
141     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)
143 jmc 1.18 e12Loc(i,j,bi,bj) = 0.5 _d 0 * (
144     & dudy(i,j) + dvdx(i,j)
145     & - k1AtZ(i,j,bi,bj) * vave(i,j)
146     & - k2AtZ(i,j,bi,bj) * uave(i,j)
147 mlosch 1.11 & )
148 jmc 1.18 & *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)
150 mlosch 1.11 & + 2.0 _d 0 * noSlipFac * (
151 jmc 1.18 & 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
153 mlosch 1.11 & )
154     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
156     C that the following lines are not necessary
157 jmc 1.18 c$$$ & - hFacV * k1AtZ(i,j,bi,bj) * vave(i,j)
158     c$$$ & - hFacU * k2AtZ(i,j,bi,bj) * uave(i,j)
159 mlosch 1.11 ENDDO
160     ENDDO
161    
162     ENDDO
163     ENDDO
164 gforget 1.16
165     #ifdef ALLOW_AUTODIFF_TAMC
166     #ifdef SEAICE_DYN_STABLE_ADJOINT
167     cgf zero out adjoint fields to stabilize pkg/seaice dyna. adjoint
168     CALL ZERO_ADJ( 1, e11Loc, myThid)
169     CALL ZERO_ADJ( 1, e12Loc, myThid)
170     CALL ZERO_ADJ( 1, e22Loc, myThid)
171     #endif
172     #endif /* ALLOW_AUTODIFF_TAMC */
173    
174 mlosch 1.1 #endif /* SEAICE_ALLOW_DYNAMICS */
175     #endif /* SEAICE_CGRID */
176     RETURN
177     END

  ViewVC Help
Powered by ViewVC 1.1.22