/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/streamice_forced_buttress.F
ViewVC logotype

Annotation of /MITgcm_contrib/dgoldberg/streamice/streamice_forced_buttress.F

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


Revision 1.1 - (hide annotations) (download)
Wed Aug 27 19:29:13 2014 UTC (10 years, 10 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
updating contrib streamice repo with latest files, and separated out convergence checks; and parameterised maximum iteration counts and interface w shelfice for coupling

1 dgoldberg 1.1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_forced_buttress.F,v 1.2 2014/06/04 12:56:40 dgoldberg Exp $
2     C $Name: $
3    
4     #include "STREAMICE_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8     CBOP
9     SUBROUTINE STREAMICE_FORCED_BUTTRESS( myThid )
10     ! O taudx,
11     ! O taudy )
12    
13     C /============================================================\
14     C | SUBROUTINE |
15     C | o |
16     C |============================================================|
17     C | |
18     C \============================================================/
19     IMPLICIT NONE
20    
21     C === Global variables ===
22     #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "GRID.h"
26     #include "STREAMICE.h"
27     #include "STREAMICE_CG.h"
28    
29     C !INPUT/OUTPUT ARGUMENTS
30     INTEGER myThid
31     ! _RL taudx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
32     ! _RL taudx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
33    
34     #ifdef ALLOW_STREAMICE
35     #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
36    
37     C LOCAL VARIABLES
38     INTEGER i, j, bi, bj, k, l
39     LOGICAL at_west_bdry, at_east_bdry,
40     & at_north_bdry, at_south_bdry
41     _RL unconf_stress
42    
43    
44     DO bj = myByLo(myThid), myByHi(myThid)
45     DO bi = myBxLo(myThid), myBxHi(myThid)
46     DO j=1-OLy+1,sNy+OLy-1
47     DO i=1-OLy+1,sNx+OLy-1
48     ! taudx_SI(i,j,bi,bj) = 0. _d 0
49     ! taudy_SI(i,j,bi,bj) = 0. _d 0
50     if (streamice_hmask(i,j,bi,bj).eq.1.0) then
51    
52     ! baseline unconfined stress
53    
54     IF (float_frac_streamice(i,j,bi,bj) .eq. 1.0) THEN
55    
56     unconf_stress = gravity *
57     & (streamice_density * H_streamice(i,j,bi,bj)**2 -
58     #ifdef USE_ALT_RLOW
59     & streamice_density_ocean_avg * R_low_si(i,j,bi,bj)**2)
60     #else
61     & streamice_density_ocean_avg * R_low(i,j,bi,bj)**2)
62     #endif
63    
64     ELSE
65    
66     unconf_stress = streamice_density * gravity *
67     & (1-streamice_density/streamice_density_ocean_avg) *
68     & H_streamice(i,j,bi,bj)**2
69    
70     ENDIF
71    
72     ! right face
73    
74     if (streamice_ufacemask(i+1,j,bi,bj).eq.2.0) then
75    
76     do k=0,1
77     if (streamice_umask(i+1,j+k,bi,bj).eq.1.0) then
78    
79    
80     taudx_SI(i+1,j+k,bi,bj) = taudx_SI(i+1,j+k,bi,bj) +
81     & (streamice_u_normal_pert(i+1,j,bi,bj) +
82     & streamice_u_normal_stress(i+1,j,bi,bj)) *
83     & .5 * unconf_stress * dyG(i+1,j,bi,bj)
84    
85     taudy_SI(i+1,j+k,bi,bj) = taudy_SI(i+1,j+k,bi,bj) +
86     & (streamice_v_shear_pert(i+1,j,bi,bj) +
87     & streamice_v_shear_stress(i+1,j,bi,bj)) *
88     & .5 * unconf_stress * dyG(i+1,j,bi,bj)
89    
90     endif
91     enddo
92     endif
93    
94     ! left face
95    
96     if (streamice_ufacemask(i,j,bi,bj).eq.2.0) then
97    
98     do k=0,1
99     if (streamice_umask(i,j+k,bi,bj).eq.1.0) then
100    
101     taudx_SI(i,j+k,bi,bj) = taudx_SI(i,j+k,bi,bj) -
102     & (streamice_u_normal_pert(i,j,bi,bj) +
103     & streamice_u_normal_stress(i,j,bi,bj)) *
104     & .5 * unconf_stress * dyG(i,j,bi,bj)
105    
106     taudy_SI(i,j+k,bi,bj) = taudy_SI(i,j+k,bi,bj) -
107     & (streamice_v_shear_pert(i,j,bi,bj) +
108     & streamice_v_shear_stress(i,j,bi,bj)) *
109     & .5 * unconf_stress * dyG(i,j,bi,bj)
110    
111     endif
112     enddo
113     endif
114    
115     if (streamice_vfacemask(i,j+1,bi,bj).eq.2.0) then
116    
117    
118     do k=0,1
119     if (streamice_umask(i+k,j+1,bi,bj).eq.1.0) then
120    
121     taudy_SI(i+k,j+1,bi,bj) = taudy_SI(i+k,j+1,bi,bj) +
122     & (streamice_v_normal_pert(i,j+1,bi,bj) +
123     & streamice_v_normal_stress(i,j+1,bi,bj)) *
124     & .5 * dxG(i,j+1,bi,bj) * unconf_stress
125    
126     taudx_SI(i+k,j+1,bi,bj) = taudx_SI(i+k,j+1,bi,bj) +
127     & (streamice_u_shear_pert(i,j+1,bi,bj) +
128     & streamice_u_shear_stress(i,j+1,bi,bj)) *
129     & .5 * unconf_stress * dxG(i,j+1,bi,bj)
130    
131     endif
132     enddo
133     endif
134    
135     if (streamice_vfacemask(i,j,bi,bj).eq.2.0) then
136    
137     do k=0,1
138     if (streamice_umask(i+k,j,bi,bj).eq.1.0) then
139    
140     taudy_SI(i+k,j,bi,bj) = taudy_SI(i+k,j,bi,bj) -
141     & (streamice_v_normal_pert(i,j,bi,bj) +
142     & streamice_v_normal_stress(i,j,bi,bj)) *
143     & .5 * dxG(i,j,bi,bj) * unconf_stress
144    
145     taudx_SI(i+k,j,bi,bj) = taudx_SI(i+k,j,bi,bj) -
146     & (streamice_u_shear_pert(i,j,bi,bj) +
147     & streamice_u_shear_stress(i,j,bi,bj)) *
148     & .5 * unconf_stress * dxG(i,j,bi,bj)
149    
150     endif
151     enddo
152     endif
153     END IF
154     ENDDO
155     ENDDO
156     ENDDO
157     ENDDO
158     #endif
159     #endif
160     RETURN
161     END
162    
163    

  ViewVC Help
Powered by ViewVC 1.1.22