/[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.2 - (show annotations) (download)
Tue Nov 12 20:47:27 2002 UTC (21 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint47a_post, checkpoint47
Changes since 1.1: +108 -0 lines
Merging from release1_p8 branch:
o New package: pkg/seaice
  Sea ice model by D. Menemenlis (JPL) and Jinlun Zhang (Seattle).
  The sea-ice code is based on Hibler (1979-1980).
  Two sea-ice dynamic solvers, ADI and LSR, are included.
  In addition to computing prognostic sea-ice variables and diagnosing
  the forcing/external data fields that drive the ocean model,
  SEAICE_MODEL also sets theta to the freezing point under sea-ice.
  The implied surface heat flux is then stored in variable
  surfaceTendencyTice, which is needed by KPP package (kpp_calc.F and
  kpp_transport_t.F) to diagnose surface buoyancy fluxes and for the
  non-local transport term.  Because this call precedes model
  thermodynamics, temperature under sea-ice may not be "exactly" at
  the freezing point by the time theta is dumped or time-averaged.

1 C $Header:
2
3 #include "SEAICE_OPTIONS.h"
4
5 CStartOfInterface
6 SUBROUTINE ostres( DWATN, COR_ICE, myThid )
7 C /==========================================================\
8 C | SUBROUTINE ostres |
9 C | o Calculate ocean surface stress |
10 C |==========================================================|
11 C \==========================================================/
12 IMPLICIT NONE
13
14 C === Global variables ===
15 #include "SIZE.h"
16 #include "EEPARAMS.h"
17 #include "PARAMS.h"
18 #include "FFIELDS.h"
19 #include "SEAICE.h"
20 #include "SEAICE_PARAMS.h"
21
22 C === Routine arguments ===
23 C myThid - Thread no. that called this routine.
24 _RL DWATN (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
25 _RL COR_ICE (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
26 INTEGER myThid
27 CEndOfInterface
28
29 #ifdef ALLOW_SEAICE
30
31 C === Local variables ===
32 C i,j,k,bi,bj - Loop counters
33
34 INTEGER i, j, k, bi, bj, IWIND
35 _RL SINWIN, COSWIN, SINWAT, COSWAT
36
37 C 25 DEG GIVES SIN EQUAL TO 0.4226
38 SINWIN=0.4226
39 COSWIN=0.9063
40 SINWAT=0.4226
41 COSWAT=0.9063
42 c do not introduce turning angle
43 SINWIN=0.0
44 COSWIN=1.0
45 SINWAT=0.0
46 COSWAT=1.0
47
48 #ifdef SEAICE_ALLOW_DYNAMICS
49 IF ( SEAICEuseDYNAMICS ) THEN
50 C-- Compute ice-affected wind stress
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 WINDX(I,J,bi,bj)=DWATN(I,J,bi,bj)
56 & *(COSWAT*(GWATX(I,J,bi,bj)-UICE(I,J,1,bi,bj))
57 & -SINWAT*(GWATY(I,J,bi,bj)-VICEC(I,J,bi,bj)))
58 WINDY(I,J,bi,bj)=DWATN(I,J,bi,bj)
59 & *(SINWAT*(GWATX(I,J,bi,bj)-UICEC(I,J,bi,bj))
60 & +COSWAT*(GWATY(I,J,bi,bj)-VICE(I,J,1,bi,bj)))
61 WINDX(I,J,bi,bj)=WINDX(I,J,bi,bj)-( COR_ICE(I,J,bi,bj)
62 & *GWATY(I,J,bi,bj)-COR_ICE(I,J,bi,bj)*VICEC(I,J,bi,bj))
63 WINDY(I,J,bi,bj)=WINDY(I,J,bi,bj)-(-COR_ICE(I,J,bi,bj)
64 & *GWATX(I,J,bi,bj)+COR_ICE(I,J,bi,bj)*UICEC(I,J,bi,bj))
65 WINDX(I,J,bi,bj)=WINDX(I,J,bi,bj)-(UICE(I,J,1,bi,bj)
66 & -UICE(I,J,3,bi,bj))*AMASS(I,J,bi,bj)/DELTAT*2.0
67 WINDY(I,J,bi,bj)=WINDY(I,J,bi,bj)-(VICE(I,J,1,bi,bj)
68 & -VICE(I,J,3,bi,bj))*AMASS(I,J,bi,bj)/DELTAT*2.0
69 ENDDO
70 ENDDO
71 ENDDO
72 ENDDO
73 DO bj=myByLo(myThid),myByHi(myThid)
74 DO bi=myBxLo(myThid),myBxHi(myThid)
75 DO j=1,sNy
76 DO i=1,sNx
77 WINDX(I,J,bi,bj)=-WINDX(I,J,bi,bj)
78 WINDY(I,J,bi,bj)=-WINDY(I,J,bi,bj)
79 ENDDO
80 ENDDO
81 ENDDO
82 ENDDO
83 ENDIF
84 #endif SEAICE_ALLOW_DYNAMICS
85
86 C-- Update overlap regions for PRESS
87 _EXCH_XY_R8(WINDX, myThid)
88 _EXCH_XY_R8(WINDY, myThid)
89
90 C Interpolate wind stress (N/m^2) to C-grid for forcing ocean model
91 DO bj=myByLo(myThid),myByHi(myThid)
92 DO bi=myBxLo(myThid),myBxHi(myThid)
93 DO j=1,sNy
94 DO i=1,sNx
95 fu(I,J,bi,bj)=0.5*(WINDX(I-1,J-1,bi,bj)+WINDX(I-1,J,bi,bj))
96 fv(I,J,bi,bj)=0.5*(WINDY(I-1,J-1,bi,bj)+WINDY(I,J-1,bi,bj))
97 ENDDO
98 ENDDO
99 ENDDO
100 ENDDO
101
102 _EXCH_XY_R4( fu, myThid )
103 _EXCH_XY_R4( fv, myThid )
104
105 #endif ALLOW_SEAICE
106
107 RETURN
108 END

  ViewVC Help
Powered by ViewVC 1.1.22