/[MITgcm]/MITgcm/pkg/streamice/streamice_upd_ffrac_uncoupled.F
ViewVC logotype

Contents of /MITgcm/pkg/streamice/streamice_upd_ffrac_uncoupled.F

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


Revision 1.4 - (show annotations) (download)
Wed Jul 1 16:34:53 2015 UTC (8 years, 10 months ago) by dgoldberg
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65n, checkpoint65o, HEAD
Changes since 1.3: +11 -8 lines
fix to avoid recomputation loop

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_upd_ffrac_uncoupled.F,v 1.3 2015/06/30 11:20:05 dgoldberg Exp $
2 C $Name: $
3
4
5 C this needs changes
6
7 #include "STREAMICE_OPTIONS.h"
8
9 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
10 CBOP 0
11 SUBROUTINE STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
12
13 C !DESCRIPTION:
14 C Initialize STREAMICE variables and constants.
15
16 C !USES:
17 IMPLICIT NONE
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "STREAMICE.h"
22 #include "GRID.h"
23
24 C !INPUT PARAMETERS:
25 INTEGER myThid
26 CEOP
27
28 #ifdef ALLOW_STREAMICE
29
30 INTEGER bi, bj, i, j
31 _RL OD, rhoi, rhow, delta, r, h, hf, i_r, rlo
32 #ifdef STREAMICE_SMOOTH_FLOATATION
33 _RL ETA_GL_STREAMICE
34 external ETA_GL_STREAMICE
35 _RL PHI_GL_STREAMICE
36 external PHI_GL_STREAMICE
37 #endif
38 #ifdef STREAMICE_FIRN_CORRECTION
39 _RL firn_depth
40 #endif
41
42 rhoi = streamice_density
43 rhow = streamice_density_ocean_avg
44 r=rhoi/rhow
45 i_r = 1/r
46 delta=1-r
47 #ifdef STREAMICE_FIRN_CORRECTION
48 firn_depth = streamice_density *
49 & streamice_firn_correction
50 & / (streamice_density-streamice_density_firn)
51 #endif
52
53
54 #ifdef STREAMICE_SMOOTH_FLOATATION
55
56 DO bj = myByLo(myThid), myByHi(myThid)
57 DO bi = myBxLo(myThid), myBxHi(myThid)
58 DO j=1-Oly,sNy+Oly
59 DO i=1-Olx,sNx+Olx
60 if (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or.
61 & STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN
62
63
64 if (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or.
65 & STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN
66
67 h = H_streamice(i,j,bi,bj)
68
69 # ifdef USE_ALT_RLOW
70 hf = -1.0 * i_r * R_low_si (i,j,bi,bj)
71 # else
72 hf = -1.0 * i_r * R_low (i,j,bi,bj)
73 # endif
74
75 surf_el_streamice(i,j,bi,bj) =
76 & ETA_GL_STREAMICE (
77 & h-hf,
78 & delta,
79 & 1. _d 0,
80 & delta*hf,
81 & streamice_smooth_gl_width)
82
83 base_el_streamice(i,j,bi,bj) =
84 & surf_el_streamice(i,j,bi,bj) - h
85
86 float_frac_streamice(i,j,bi,bj) =
87 & PHI_GL_STREAMICE (
88 & h-hf,
89 & streamice_smooth_gl_width)
90
91 ENDIF
92 ENDIF
93 ENDDO
94 ENDDO
95 ENDDO
96 ENDDO
97
98 #else
99 ! STREAMICE_SMOOTH_FLOATATION
100
101 DO bj = myByLo(myThid), myByHi(myThid)
102 DO bi = myBxLo(myThid), myBxHi(myThid)
103 DO j=1-Oly,sNy+Oly
104 DO i=1-Olx,sNx+Olx
105 # ifdef USE_ALT_RLOW
106 rlo = R_low_si (i,j,bi,bj)
107 # else
108 rlo = R_low (i,j,bi,bj)
109 #endif
110
111 #ifdef STREAMICE_FIRN_CORRECTION
112 if (STREAMICE_apply_firn_correction) then
113 ! h=h_streamice(i,j,bi,bj)
114 if (h_streamice(i,j,bi,bj).lt.firn_depth) then
115 OD = -1.0 * rlo - streamice_density_firn/rhow *
116 & h_streamice(i,j,bi,bj)
117 else
118 OD = -1.0 * rlo - rhoi/rhow *
119 & (h_streamice(i,j,bi,bj)-streamice_firn_correction)
120 endif
121 else
122 #endif
123 OD = -1.0 * Rlo -
124 & H_streamice(i,j,bi,bj) * rhoi/rhow
125 #ifdef STREAMICE_FIRN_CORRECTION
126 endif
127 #endif
128
129 IF (OD .ge. 0. _d 0) THEN
130
131 c ice thickness does not take up whole ocean column -> floating
132 float_frac_streamice(i,j,bi,bj) = 0.0
133 base_el_streamice(i,j,bi,bj) = Rlo+OD
134 #ifdef STREAMICE_FIRN_CORRECTION
135 if (STREAMICE_apply_firn_correction) then
136 if (h_streamice(i,j,bi,bj).lt.firn_depth) then
137 surf_el_streamice(i,j,bi,bj) =
138 & (1-streamice_density_firn/rhow)*h_streamice(i,j,bi,bj)
139 else
140 surf_el_streamice(i,j,bi,bj) =
141 & (1-rhoi/rhow)*h_streamice(i,j,bi,bj) +
142 & rhoi/rhow*streamice_firn_correction
143 endif
144 else
145 #endif
146 surf_el_streamice(i,j,bi,bj) =
147 & (1-rhoi/rhow)*H_streamice(i,j,bi,bj)
148 #ifdef STREAMICE_FIRN_CORRECTION
149 endif
150 #endif
151
152 ELSE
153
154
155 float_frac_streamice(i,j,bi,bj) = 1.0
156 base_el_streamice(i,j,bi,bj) = Rlo
157 surf_el_streamice(i,j,bi,bj) = Rlo
158 & + H_streamice(i,j,bi,bj)
159 ENDIF
160 ENDDO
161 ENDDO
162 ENDDO
163 ENDDO
164
165 #endif
166
167 _EXCH_XY_RL(float_frac_streamice, myThid )
168 _EXCH_XY_RL(base_el_streamice, myThid )
169 _EXCH_XY_RL(surf_el_streamice, myThid )
170
171
172
173
174 #endif /* ALLOW_STREAMICE */
175
176 RETURN
177 END

  ViewVC Help
Powered by ViewVC 1.1.22