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

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

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

revision 1.8 by mlosch, Mon Mar 20 21:36:11 2006 UTC revision 1.21 by dimitri, Thu Jan 17 23:18:39 2008 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  #include "SEAICE_OPTIONS.h"  #include "SEAICE_OPTIONS.h"
5    
6  CStartOfInterface  CStartOfInterface
7        SUBROUTINE SEAICE_OCEAN_STRESS(        SUBROUTINE SEAICE_OCEAN_STRESS(
8       I     myTime, myIter, myThid )       I     myTime, myIter, myThid )
9  C     /==========================================================\  C     /==========================================================\
10  C     | SUBROUTINE SEAICE_OCEAN_STRESS                           |  C     | SUBROUTINE SEAICE_OCEAN_STRESS                           |
# Line 18  C     === Global variables === Line 18  C     === Global variables ===
18  #include "SIZE.h"  #include "SIZE.h"
19  #include "EEPARAMS.h"  #include "EEPARAMS.h"
20  #include "PARAMS.h"  #include "PARAMS.h"
21    #include "DYNVARS.h"
22  #include "GRID.h"  #include "GRID.h"
23  #include "FFIELDS.h"  #include "FFIELDS.h"
24  #include "SEAICE.h"  #include "SEAICE.h"
25  #include "SEAICE_PARAMS.h"  #include "SEAICE_PARAMS.h"
 #include "SEAICE_FFIELDS.h"  
26    
27  C     === Routine arguments ===  C     === Routine arguments ===
28  C     myTime - Simulation time  C     myTime - Simulation time
# Line 33  C     myThid - Thread no. that called th Line 33  C     myThid - Thread no. that called th
33        INTEGER myThid        INTEGER myThid
34  CEndOfInterface  CEndOfInterface
35    
36  #ifdef SEAICE_CGRID  #ifdef SEAICE_CGRID
37  C     === Local variables ===  C     === Local variables ===
38  C     i,j,bi,bj - Loop counters  C     i,j,bi,bj - Loop counters
39    
40        INTEGER i, j, bi, bj        INTEGER i, j, bi, bj
41        _RL  SINWAT, COSWAT, SINWIN, COSWIN        _RL  SINWAT, COSWAT, SINWIN, COSWIN
42        _RL  fuIce, fvIce, FX, FY        _RL  fuIceLoc, fvIceLoc, FX, FY
43        _RL  areaW, areaS        _RL  areaW, areaS
44    
45          _RL e11         (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
46          _RL e22         (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
47          _RL e12         (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
48        _RL press       (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)        _RL press       (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
49        _RL etaPlusZeta (1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL sig11       (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
50        _RL zetaMinusEta(1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL sig22       (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
51        _RL etaMeanZ    (1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL sig12       (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
52        _RL etaMeanU    (1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL eplus, eminus
       _RL etaMeanV    (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL dVdx        (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL dVdy        (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL dUdx        (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
       _RL dUdy        (1-Olx:sNx+Olx,1-Oly:sNy+Oly)  
53    
54  c     introduce turning angle (default is zero)  c     introduce turning angle (default is zero)
55        SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)        SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)
# Line 59  c     introduce turning angle (default i Line 57  c     introduce turning angle (default i
57        SINWIN=SIN(SEAICE_airTurnAngle*deg2rad)        SINWIN=SIN(SEAICE_airTurnAngle*deg2rad)
58        COSWIN=COS(SEAICE_airTurnAngle*deg2rad)        COSWIN=COS(SEAICE_airTurnAngle*deg2rad)
59    
 C--   Update overlap regions  
       CALL EXCH_UV_XY_RL(WINDX, WINDY, .TRUE., myThid)  
   
 #ifndef SEAICE_EXTERNAL_FLUXES  
 C--   Interpolate wind stress (N/m^2) from C-points of C-grid  
 C     to U and V points of C-grid for forcing the ocean model.  
       DO bj=myByLo(myThid),myByHi(myThid)  
        DO bi=myBxLo(myThid),myBxHi(myThid)  
         DO j=1,sNy  
          DO i=1,sNx  
           fu(I,J,bi,bj)=0.5*(WINDX(I,J,bi,bj) + WINDX(I-1,J,bi,bj))  
           fv(I,J,bi,bj)=0.5*(WINDY(I,J,bi,bj) + WINDY(I,J-1,bi,bj))  
          ENDDO  
         ENDDO  
        ENDDO  
       ENDDO  
 #endif /* ifndef SEAICE_EXTERNAL_FLUXES */  
   
60        IF ( useHB87StressCoupling ) THEN        IF ( useHB87StressCoupling ) THEN
61  C  C
62  C     use an intergral over ice and ocean surface layer to define  C     use an intergral over ice and ocean surface layer to define
63  C     surface stresses on ocean following Hibler and Bryan (1987, JPO)  C     surface stresses on ocean following Hibler and Bryan (1987, JPO)
64  C      C
65  C     recompute viscosities from updated ice velocities  C     recompute strain rates, viscosities, etc. from updated ice velocities
66         CALL SEAICE_CALC_VISCOSITIES(         IF ( .NOT. SEAICEuseEVP ) THEN
67       I      uIce(1-Olx,1-Oly,1,1,1), vIce(1-Olx,1-Oly,1,1,1),  C     only for EVP we already have the stress components otherwise we need
68       I      zMin, zMax, hEffM, press0,  C     to recompute them here
69       O      eta, zeta, press,          CALL SEAICE_CALC_STRAINRATES(
70  #ifdef SEAICE_ALLOW_EVP       I       uIce, vIce,
71       O      seaice_div, seaice_tension, seaice_shear,       O       e11, e22, e12,
72  #endif /* SEAICE_ALLOW_EVP */       I       3, 3, myTime, myIter, myThid )
73       I      myThid )  
74            CALL SEAICE_CALC_VISCOSITIES(
75         I       e11, e22, e12, zMin, zMax, hEffM, press0,
76         O       eta, zeta, press,
77         I       3, myTime, myIter, myThid )
78           ENDIF
79  C     re-compute internal stresses with updated ice velocities  C     re-compute internal stresses with updated ice velocities
80         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
81          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
82           DO j=1-Oly+1,sNy+Oly-1           IF ( .NOT. SEAICEuseEVP ) THEN
83            DO i=1-Olx+1,sNx+Olx-1  C     only for EVP we already have computed the stress divergences, for
84             etaPlusZeta (I,J) =  eta(I,J,bi,bj) + zeta(I,J,bi,bj)  C     anything else we have to do it here
85             zetaMinusEta(I,J) = zeta(I,J,bi,bj) -  eta(I,J,bi,bj)            DO j=1-Oly,sNy+Oly
86             etaMeanU (I,J) =             DO i=1-Olx,sNx+Olx
87       &          HALF*(ETA (I,J,bi,bj) + ETA (I-1,J  ,bi,bj))              sig11(I,J) = 0. _d 0
88             etaMeanV (I,J) =              sig22(I,J) = 0. _d 0
89       &          HALF*(ETA (I,J,bi,bj) + ETA (I  ,J-1,bi,bj))              sig12(I,J) = 0. _d 0
90             etaMeanZ (I,J) = QUART *               ENDDO
      &          ( eta(I  ,J,bi,bj) + eta(I  ,J-1,bi,bj)  
      &          + eta(I-1,J,bi,bj) + eta(I-1,J-1,bi,bj) )  
            dUdx(I,J) = ( uIce(I+1,J,1,bi,bj) - uIce(I,J,1,bi,bj) )  
      &          * _recip_dxF(I,J,bi,bj)  
            dUdy(I,J) = ( uIce(I,J+1,1,bi,bj) - uIce(I,J,1,bi,bj) )  
      &          * _recip_dyU(I,J+1,bi,bj)  
            dVdx(I,J) = ( vIce(I+1,J,1,bi,bj) - vIce(I,J,1,bi,bj) )  
      &          * _recip_dxV(I+1,J,bi,bj)  
            dVdy(I,J) = ( vIce(I,J+1,1,bi,bj) - vIce(I,J,1,bi,bj) )  
      &          * _recip_dyF(I,J,bi,bj)  
91            ENDDO            ENDDO
92           ENDDO  
93           DO J = 1,sNy            DO j=0,sNy
94            DO I = 1,sNx             DO i=0,sNx
95  C     First FX = (d/dx)*sigma              eplus = e11(I,J,bi,bj) + e22(I,J,bi,bj)
96  C     + d/dx[ eta+zeta d/dx ] U              eminus= e11(I,J,bi,bj) - e22(I,J,bi,bj)
97             FX = _recip_dxC(I,J,bi,bj) *              sig11(I,J) = zeta(I,J,bi,bj)*eplus + eta(I,J,bi,bj)*eminus
98       &            ( etaPlusZeta(I  ,J) * dUdx(I  ,J)       &           - 0.5 _d 0 * PRESS(I,J,bi,bj)
99       &            - etaPlusZeta(I-1,J) * dUdx(I-1,J) )              sig22(I,J) = zeta(I,J,bi,bj)*eplus - eta(I,J,bi,bj)*eminus
100  C     + (d/dy)[eta*(d/dy + tanphi/a)] U (also on UVRT1/2)       &           - 0.5 _d 0 * PRESS(I,J,bi,bj)
101             FX = FX + _recip_dyG(I,J,bi,bj) * (             ENDDO
102       &          ( etaMeanZ(I,J+1) * dUdy(I,J+1)            ENDDO
103       &          - etaMeanZ(I,J  ) * dUdy(I,J  )  
104       &          )            DO j=1,sNy+1
105       &          - ( etaMeanZ(I,J+1)             DO i=1,sNx+1
106       &            * ( uIce(I,J+1,1,bi,bj)+uIce(I,J,1,bi,bj) )              sig12(I,J) = 2. _d 0 * e12(I,J,bi,bj) *
107       &            - etaMeanZ(I,J  )       &           ( eta(I,J  ,bi,bj) + eta(I-1,J  ,bi,bj)
108       &            * ( uIce(I,J-1,1,bi,bj)+uIce(I,J,1,bi,bj) ) )       &           + eta(I,J-1,bi,bj) + eta(I-1,J-1,bi,bj) )
109       &          * 0.5 _d 0 * _tanPhiAtU(I,J,bi,bj)       &           /MAX(1. _d 0,
110       &          * recip_rSphere )       &             hEffM(I,J  ,bi,bj) + hEffM(I-1,J  ,bi,bj)
111  C     - 2*eta*(tanphi/a) * ( tanphi/a ) U       &           + hEffM(I,J-1,bi,bj) + hEffM(I-1,J-1,bi,bj))
112             FX = FX - TWO * uIce(I,J,1,bi,bj)             ENDDO
113       &          * etaMeanU(I,J)*recip_rSphere*recip_rSphere            ENDDO
114       &          * _tanPhiAtU(I,J,bi,bj)  * _tanPhiAtU(I,J,bi,bj)  C     evaluate divergence of stress and apply to forcing
115  C     + d/dx[ (zeta-eta) dV/dy]            DO J=1,sNy
116             FX = FX +             DO I=1,sNx
117       &          ( zetaMinusEta(I  ,J  ) * dVdy(I  ,J  )              FX = ( sig11(I  ,J  ) * _dyF(I  ,J  ,bi,bj)
118       &          - zetaMinusEta(I-1,J  ) * dVdy(I-1,J  )       &           - sig11(I-1,J  ) * _dyF(I-1,J  ,bi,bj)
119       &          ) * _recip_dxC(I,J,bi,bj)       &           + sig12(I  ,J+1) * _dxV(I  ,J+1,bi,bj)
120  C     + d/dy[ eta dV/x ]       &           - sig12(I  ,J  ) * _dxV(I  ,J  ,bi,bj)
121             FX = FX + (       &           ) * recip_rAw(I,J,bi,bj)
122       &            etaMeanZ(I,J+1)       &           -
123       &          * ( vIce(I  ,J+1,1,bi,bj) - vIce(I-1,J+1,1,bi,bj) )       &           ( sig12(I,J) + sig12(I,J+1) )
124       &          * _recip_dxV(I,J+1,bi,bj)       &           * _tanPhiAtU(I,J,bi,bj) * recip_rSphere
125       &          - etaMeanZ(I,J  )       &           +
126       &          * ( vIce(I  ,J,1,bi,bj) - vIce(I-1,J,1,bi,bj) )       &           ( sig22(I,J) + sig22(I-1,J) ) * 0.5 _d 0
127       &          * _recip_dxV(I,J,bi,bj)       &           * _tanPhiAtU(I,J,bi,bj) * recip_rSphere
128       &          ) * _recip_dyG(I,J,bi,bj)  C     one metric term  missing for general curvilinear coordinates
129  C     - d/dx[ (eta+zeta) * v * (tanphi/a) ]              FY = ( sig22(I  ,J  ) * _dxF(I  ,J  ,bi,bj)
130             FX = FX - (       &           - sig22(I  ,J-1) * _dxF(I  ,J-1,bi,bj)
131       &            etaPlusZeta(I  ,J)       &           + sig12(I+1,J  ) * _dyU(I+1,J  ,bi,bj)
132       &          * 0.5 * (vIce(I  ,J,1,bi,bj)+vIce(I  ,J+1,1,bi,bj))       &           - sig12(I  ,J  ) * _dyU(I  ,J  ,bi,bj)
133       &          * 0.5 * ( _tanPhiAtU(I  ,J,bi,bj)       &           ) * recip_rAs(I,J,bi,bj)
134       &          + _tanPhiAtU(I+1,J,bi,bj) )       &           -
135       &          - etaPlusZeta(I-1,J) *       &           ( sig22(I,J) + sig22(I,J-1) ) * 0.5 _d 0
136       &          * 0.5 * (vIce(I-1,J,1,bi,bj)+vIce(I-1,J+1,1,bi,bj))       &           * _tanPhiAtV(I,J,bi,bj) * recip_rSphere
137       &          * 0.5 * ( _tanPhiAtU(I-1,J,bi,bj)  C     two metric terms missing for general curvilinear coordinates
138       &          + _tanPhiAtU(I  ,J,bi,bj) )  C     average wind stress over ice and ocean and apply averaged wind
139       &          )* _recip_dxC(I,J,bi,bj)*recip_rSphere  C     stress and internal ice stresses to surface layer of ocean
140  C     - 2*eta*(tanphi/a) * dV/dx              areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
141             FX = FX       &           * SEAICEstressFactor
142       &          -TWO * etaMeanU(I,J) * _tanPhiAtV(I,J,bi,bj)              areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))
143       &          *recip_rSphere       &           * SEAICEstressFactor
144       &          *(vIce(I  ,J,1,bi,bj) + vIce(I  ,J+1,1,bi,bj)              fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)
145       &          - vIce(I-1,J,1,bi,bj) - vIce(I-1,J+1,1,bi,bj))       &           + areaW*taux(I,J,bi,bj)
146       &          * _recip_dxC(I,J,bi,bj)       &           + FX * SEAICEstressFactor
147  C     - (d/dx) P/2              fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)
148             FX = _maskW(I,J,1,bi,bj) * ( FX - _recip_dxC(I,J,bi,bj)       &           + areaS*tauy(I,J,bi,bj)
149       &          * ( press(I,J,bi,bj) - press(I-1,J,bi,bj) ) )       &           + FY * SEAICEstressFactor
150  C  C     save stress divergence for later
151  C     then FY = (d/dy)*sigma  #ifdef SEAICE_ALLOW_EVP
152  C     + d/dy [(eta+zeta) d/dy] V              stressDivergenceX(I,J,bi,bj) = FX
153             FY = _recip_dyC(I,J,bi,bj) *              stressDivergenceY(I,J,bi,bj) = FY
154       &          ( dVdy(I,J  ) * etaPlusZeta(I,J  )  #endif /* SEAICE_ALLOW_EVP */
155       &          - dVdy(I,J-1) * etaPlusZeta(I,J-1) )             ENDDO
156  C     + d/dx [eta d/dx] V            ENDDO
157             FY = FY +  _recip_dxC(I,J,bi,bj) *           ELSE
158       &          ( eta(I  ,J,bi,bj) * dVdx(I  ,J)  #ifdef SEAICE_ALLOW_EVP
159       &          - eta(I-1,J,bi,bj) * dVdx(I-1,J) )            DO J=1,sNy
160  C     - d/dy [(zeta-eta) tanphi/a] V             DO I=1,sNx
161             FY = FY - _recip_dyC(I,J,bi,bj) * recip_rSphere * (  C     average wind stress over ice and ocean and apply averaged wind
      &            zetaMinusEta(I,J  ) * tanPhiAtU(I,J  ,bi,bj)  
      &          * 0.5 * ( vIce(I,J,1,bi,bj) + vIce(I,J+1,1,bi,bj))  
      &          - zetaMinusEta(I,J-1) * tanPhiAtU(I,J-1,bi,bj)  
      &          * 0.5 * ( vIce(I,J,1,bi,bj) + vIce(I,J-1,1,bi,bj)) )  
 C     2*eta tanphi/a ( - tanphi/a - d/dy) V  
            FY = FY - TWO*etaMeanV(I,J) * recip_rSphere  
      &          * _tanPhiAtV(I,J,bi,bj) * (  
      &            _tanPhiAtV(I,J,bi,bj) * recip_rSphere  
      &          + _recip_dyC(I,J,bi,bj) *  
      &          ( 0.5 * ( vIce(I,J,1,bi,bj) + vIce(I,J+1,1,bi,bj))  
      &          - 0.5 * ( vIce(I,J,1,bi,bj) + vIce(I,J-1,1,bi,bj)) ) )  
 C     + d/dy[ (zeta-eta) dU/dx ]  
            FY = FY +  
      &          ( zetaMinusEta(I,J  )*dUdx(I,J  )  
      &          - zetaMinusEta(I,J-1)*dUdx(I,J-1) )  
      &          * _recip_dyC(I,J,bi,bj)  
 C     + d/dx[ eta dU/dy ]  
            FY = FY + _recip_dxG(I,J,bi,bj) *  
      &          ( etaMeanZ(I+1,J) * dUdy(I+1,J)  
      &          - etaMeanZ(I  ,J) * dUdy(I  ,J) )  
 C     + d/dx[ eta * (tanphi/a) * U ]  
            FY = FY + (  
      &            etaMeanZ(I+1,J) * 0.5 *  
      &          ( uIce(I+1,J  ,1,bi,bj) * _tanPhiAtU(I+1,J  ,bi,bj)  
      &          + uIce(I+1,J-1,1,bi,bj) * _tanPhiAtU(I+1,J-1,bi,bj) )  
      &          - etaMeanZ(I  ,J) * 0.5 *  
      &          ( uIce(I  ,J  ,1,bi,bj) * _tanPhiAtU(I  ,J  ,bi,bj)  
      &          + uIce(I  ,J-1,1,bi,bj) * _tanPhiAtU(I  ,J  ,bi,bj) )  
      &          ) *  _recip_dxG(I,J,bi,bj)*recip_rSphere  
 C     + 2*eta*(tanphi/a) dU/dx  
            FY = FY +  
      &          TWO * etaMeanV(I,J)*TWO  * _tanPhiAtV(I,J,bi,bj)  
      &          * ( uIce(I+1,J,1,bi,bj)+uIce(I+1,J-1,1,bi,bj)  
      &            - uIce(I  ,J,1,bi,bj)-uIce(I  ,J-1,1,bi,bj) )  
      &          * _recip_dxG(I,J,bi,bj) * recip_rSphere  
 C     - (d/dy) P/2  
            FY = _maskS(I,J,1,bi,bj) * ( FY - _recip_dyC(I,J,bi,bj)  
      &          * ( press(I,J,bi,bj) - press(I,J-1,bi,bj) ) )  
 C      
 C     recompute wind stress over ice (done already in seaice_dynsolver,  
 C     but not saved)  
            fuIce = 0.5 _d 0 *  
      &          ( DAIRN(I  ,J,bi,bj)*(  
      &          COSWIN*uWind(I  ,J,bi,bj)  
      &          -SIGN(SINWIN, _fCori(I  ,J,bi,bj))*vWind(I  ,J,bi,bj) )  
      &          + DAIRN(I-1,J,bi,bj)*(  
      &          COSWIN*uWind(I-1,J,bi,bj)  
      &          -SIGN(SINWIN, _fCori(I-1,J,bi,bj))*vWind(I-1,J,bi,bj) )  
      &          )  
            fvIce = 0.5 _d 0 *  
      &          ( DAIRN(I,J  ,bi,bj)*(  
      &          SIGN(SINWIN, _fCori(I  ,J,bi,bj))*uWind(I,J  ,bi,bj)  
      &          +COSWIN*vWind(I,J  ,bi,bj) )  
      &          + DAIRN(I,J-1,bi,bj)*(  
      &          SIGN(SINWIN, _fCori(I,J-1,bi,bj))*uWind(I,J-1,bi,bj)  
      &          +COSWIN*vWind(I,J-1,bi,bj) )  
      &          )  
 C     average wind stress over ice and ocean and apply averaged wind  
162  C     stress and internal ice stresses to surface layer of ocean  C     stress and internal ice stresses to surface layer of ocean
163             areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))              areaW = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
164             areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))       &           * SEAICEstressFactor
165             fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)+areaW*fuIce + FX              areaS = 0.5 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))
166             fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)+areaS*fvIce + FY       &           * SEAICEstressFactor
167            END DO              fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)
168           END DO       &           + areaW*taux(I,J,bi,bj)
169         &           + stressDivergenceX(I,J,bi,bj) * SEAICEstressFactor
170                fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)
171         &           + areaS*tauy(I,J,bi,bj)
172         &           + stressDivergenceY(I,J,bi,bj) * SEAICEstressFactor
173               ENDDO
174              ENDDO
175    #endif /* SEAICE_ALLOW_EVP */
176             ENDIF
177          ENDDO          ENDDO
178         ENDDO         ENDDO
179    
180        ELSE        ELSE
181    C     else: useHB87StressCoupling=F
182    
183  C--   Compute ice-affected wind stress (interpolate to U/V-points)  C--   Compute ice-affected wind stress (interpolate to U/V-points)
184  C     by averaging wind stress and ice-ocean stress according to  C     by averaging wind stress and ice-ocean stress according to
185  C     ice cover  C     ice cover
186        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
187         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
188          DO j=1,sNy          DO j=1,sNy
189           DO i=1,sNx           DO i=1,sNx
190            fuIce=HALF*( DWATN(I,J,bi,bj)+DWATN(I,J+1,bi,bj) )*            fuIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I-1,J,bi,bj) )*
191       &         COSWAT *       &         COSWAT *
192       &         ( UICE(I,J,1,bi,bj)-GWATX(I,J,bi,bj) )       &         ( UICE(I,J,1,bi,bj)-uVel(I,J,1,bi,bj) )
193       &         - SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *       &         - SIGN(SINWAT, _fCori(I,J,bi,bj)) * 0.5 _d 0 *
194       &         ( DWATN(I  ,J,bi,bj) *       &         ( DWATN(I  ,J,bi,bj) *
195       &         0.5 _d 0*(vIce(I  ,J  ,1,bi,bj)-GWATY(I  ,J  ,bi,bj)       &         0.5 _d 0*(vIce(I  ,J  ,1,bi,bj)-vVel(I  ,J  ,1,bi,bj)
196       &                  +vIce(I  ,J+1,1,bi,bj)-GWATY(I  ,J+1,bi,bj))       &                  +vIce(I  ,J+1,1,bi,bj)-vVel(I  ,J+1,1,bi,bj))
197       &         + DWATN(I-1,J,bi,bj) *       &         + DWATN(I-1,J,bi,bj) *
198       &         0.5 _d 0*(vIce(I-1,J  ,1,bi,bj)-GWATY(I-1,J  ,bi,bj)       &         0.5 _d 0*(vIce(I-1,J  ,1,bi,bj)-vVel(I-1,J  ,1,bi,bj)
199       &                  +vIce(I-1,J+1,1,bi,bj)-GWATY(I-1,J+1,bi,bj))       &                  +vIce(I-1,J+1,1,bi,bj)-vVel(I-1,J+1,1,bi,bj))
200       &         )       &         )
201            fvIce=HALF*( DWATN(I,J,bi,bj)+DWATN(I+1,J,bi,bj) )*            fvIceLoc=HALF*( DWATN(I,J,bi,bj)+DWATN(I,J-1,bi,bj) )*
202       &         COSWAT *       &         COSWAT *
203       &         ( VICE(I,J,1,bi,bj)-GWATY(I,J,bi,bj) )       &         ( VICE(I,J,1,bi,bj)-vVel(I,J,1,bi,bj) )
204       &         + SIGN(SINWAT,  _fCori(I,J,bi,bj)) * 0.5 _d 0 *       &         + SIGN(SINWAT,  _fCori(I,J,bi,bj)) * 0.5 _d 0 *
205       &         ( DWATN(I,J  ,bi,bj) *       &         ( DWATN(I,J  ,bi,bj) *
206       &         0.5 _d 0*(uIce(I  ,J  ,1,bi,bj)-GWATX(I  ,J  ,bi,bj)       &         0.5 _d 0*(uIce(I  ,J  ,1,bi,bj)-uVel(I  ,J  ,1,bi,bj)
207       &                  +uIce(I+1,J  ,1,bi,bj)-GWATX(I+1,J  ,bi,bj))       &                  +uIce(I+1,J  ,1,bi,bj)-uVel(I+1,J  ,1,bi,bj))
208       &         + DWATN(I,J-1,bi,bj) *       &         + DWATN(I,J-1,bi,bj) *
209       &         0.5 _d 0*(uIce(I  ,J-1,1,bi,bj)-GWATX(I  ,J-1,bi,bj)       &         0.5 _d 0*(uIce(I  ,J-1,1,bi,bj)-uVel(I  ,J-1,1,bi,bj)
210       &                  +uIce(I+1,J-1,1,bi,bj)-GWATX(I+1,J-1,bi,bj))       &                  +uIce(I+1,J-1,1,bi,bj)-uVel(I+1,J-1,1,bi,bj))
211       &         )       &         )
212            areaW = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))            areaW = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I-1,J,1,bi,bj))
213         &         * SEAICEstressFactor
214            areaS = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))            areaS = 0.5 _d 0 * (AREA(I,J,1,bi,bj) + AREA(I,J-1,1,bi,bj))
215            fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)+areaW*fuIce       &         * SEAICEstressFactor
216            fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)+areaS*fvIce            fu(I,J,bi,bj)=(ONE-areaW)*fu(I,J,bi,bj)+areaW*fuIceLoc
217              fv(I,J,bi,bj)=(ONE-areaS)*fv(I,J,bi,bj)+areaS*fvIceLoc
218           ENDDO           ENDDO
219          ENDDO          ENDDO
220         ENDDO         ENDDO
# Line 293  C     ice cover Line 222  C     ice cover
222        ENDIF        ENDIF
223        CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)        CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
224    
225  #endif /* not SEAICE_CGRID */  #endif /* SEAICE_CGRID */
226    
227        RETURN        RETURN
228        END        END

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.21

  ViewVC Help
Powered by ViewVC 1.1.22