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

Contents of /MITgcm/pkg/seaice/ostres.F

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


Revision 1.23 - (show annotations) (download)
Wed Nov 17 14:58:23 2010 UTC (13 years, 5 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62o, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint63, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.22: +1 -47 lines
remove commented lines

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/ostres.F,v 1.22 2010/10/29 15:26:29 jmc Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE ostres( COR_ICE, myThid )
8 C *==========================================================*
9 C | SUBROUTINE ostres |
10 C | o Calculate ocean surface stress |
11 C *==========================================================*
12 C *==========================================================*
13 IMPLICIT NONE
14
15 C === Global variables ===
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "FFIELDS.h"
20 #include "SEAICE.h"
21 #include "SEAICE_PARAMS.h"
22
23 C === Routine arguments ===
24 C myThid - Thread no. that called this routine.
25 _RL COR_ICE (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
26 INTEGER myThid
27 CEndOfInterface
28
29 #ifndef SEAICE_CGRID
30 C === Local variables ===
31 C i,j,bi,bj - Loop counters
32
33 INTEGER i, j, bi, bj
34 _RL SINWIN, COSWIN, SINWAT, COSWAT
35 #ifdef SEAICE_BICE_STRESS
36 _RL fuIce, fvIce
37 #endif
38
39 c introduce turning angle (default is zero)
40 SINWIN=SIN(SEAICE_airTurnAngle*deg2rad)
41 COSWIN=COS(SEAICE_airTurnAngle*deg2rad)
42 SINWAT=SIN(SEAICE_waterTurnAngle*deg2rad)
43 COSWAT=COS(SEAICE_waterTurnAngle*deg2rad)
44
45 C-- Update overlap regions
46 CALL EXCH_UV_XY_RL(WINDX, WINDY, .TRUE., myThid)
47
48 #ifndef SEAICE_EXTERNAL_FLUXES
49 C-- Interpolate wind stress (N/m^2) from South-West B-grid
50 C to South-West C-grid for forcing ocean model.
51 DO bj=myByLo(myThid),myByHi(myThid)
52 DO bi=myBxLo(myThid),myBxHi(myThid)
53 DO j=1,sNy
54 DO i=1,sNx
55 fu(I,J,bi,bj)=HALF
56 & *(WINDX(I,J+1,bi,bj)+WINDX(I,J,bi,bj))
57 fv(I,J,bi,bj)=HALF
58 & *(WINDY(I+1,J,bi,bj)+WINDY(I,J,bi,bj))
59 ENDDO
60 ENDDO
61 ENDDO
62 ENDDO
63 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
64 #endif /* ifndef SEAICE_EXTERNAL_FLUXES */
65
66 #ifdef SEAICE_BICE_STRESS
67 C-- Compute ice-affected wind stress
68 DO bj=myByLo(myThid),myByHi(myThid)
69 DO bi=myBxLo(myThid),myBxHi(myThid)
70 DO j=1,sNy
71 DO i=1,sNx
72 fuIce=QUART*( DWATN(I,J,bi,bj)+DWATN(I,J+1,bi,bj) )*(
73 & COSWAT *
74 & ( UICE(I,J, bi,bj)-GWATX(I,J, bi,bj)
75 & + UICE(I,J+1,bi,bj)-GWATX(I,J+1,bi,bj) )
76 & -SIGN(SINWAT,COR_ICE(I,J,bi,bj)) *
77 & ( VICE(I, J,bi,bj)-GWATY(I, J,bi,bj)
78 & + VICE(I+1,J,bi,bj)-GWATY(I+1,J,bi,bj) )
79 & )
80 fvIce=QUART*( DWATN(I,J,bi,bj)+DWATN(I+1,J,bi,bj) )*(
81 & SIGN(SINWAT,COR_ICE(I,J,bi,bj)) *
82 & ( UICE(I,J, bi,bj)-GWATX(I,J, bi,bj)
83 & + UICE(I,J+1,bi,bj)-GWATX(I,J+1,bi,bj) )
84 & + COSWAT *
85 & ( VICE(I, J,bi,bj)-GWATY(I, J,bi,bj)
86 & + VICE(I+1,J,bi,bj)-GWATY(I+1,J,bi,bj) )
87 & )
88 fu(I,J,bi,bj)=(ONE-AREA(I,J,bi,bj))*fu(I,J,bi,bj)+
89 & AREA(I,J,bi,bj)*fuIce
90 fv(I,J,bi,bj)=(ONE-AREA(I,J,bi,bj))*fv(I,J,bi,bj)+
91 & AREA(I,J,bi,bj)*fvIce
92 ENDDO
93 ENDDO
94 ENDDO
95 ENDDO
96 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
97 #endif /* SEAICE_BICE_STRESS */
98 #endif /* not SEAICE_CGRID */
99
100 RETURN
101 END

  ViewVC Help
Powered by ViewVC 1.1.22