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

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

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


Revision 1.10 - (show annotations) (download)
Thu Sep 10 15:51:30 2015 UTC (8 years, 9 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65o
Changes since 1.9: +20 -5 lines
compute tensileStrength
get rid of superfluous "include tamc.h" statement

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_calc_ice_strength.F,v 1.9 2015/01/07 13:27:10 mlosch Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5 #ifdef ALLOW_AUTODIFF
6 # include "AUTODIFF_OPTIONS.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: SEAICE_CALC_ICE_STRENGTH
11 C !INTERFACE: ==========================================================
12 SUBROUTINE SEAICE_CALC_ICE_STRENGTH(
13 I bi, bj, myTime, myIter, myThid )
14
15 C !DESCRIPTION: \bv
16 C *===========================================================*
17 C | SUBROUTINE SEAICE_CALC_ICE_STRENGTH
18 C | o compute ice strengh PRESS0
19 C | according to
20 C | (a) Hibler (1979)
21 C | (b) Thorndyke et al (1975) and Hibler (1980)
22 C | (c) Bitz et al (2001) and Lipscomb et al (2007)
23 C |
24 C | Martin Losch, Apr. 2014, Martin.Losch@awi.de
25 C *===========================================================*
26 C \ev
27
28 C !USES: ===============================================================
29 IMPLICIT NONE
30
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "PARAMS.h"
34 #include "GRID.h"
35 #include "SEAICE_SIZE.h"
36 #include "SEAICE_PARAMS.h"
37 #include "SEAICE.h"
38
39 C !INPUT PARAMETERS: ===================================================
40 C === Routine arguments ===
41 C bi, bj :: outer loop counters
42 C myTime :: current time
43 C myIter :: iteration number
44 C myThid :: Thread no. that called this routine.
45 INTEGER bi,bj
46 _RL myTime
47 INTEGER myIter
48 INTEGER myThid
49 CEOP
50
51 C !LOCAL VARIABLES: ====================================================
52 C === Local variables ===
53 C i,j,k :: inner loop counters
54 C i/jMin/Max :: loop boundaries
55 C
56 INTEGER i, j
57 INTEGER iMin, iMax, jMin, jMax
58 _RL tmpscal1, tmpscal2
59 #ifdef SEAICE_ITD
60 C variables related to ridging schemes
61 C ridgingModeNorm :: norm to ensure convervation (N in Lipscomb et al 2007)
62 C partFunc :: participation function (a_n in Lipscomb et al 2007)
63 C ridgeRatio :: mean ridge thickness/ thickness of ridging ice
64 C hrMin :: min ridge thickness
65 C hrMax :: max ridge thickness (SEAICEredistFunc = 0)
66 C hrExp :: ridge e-folding scale (SEAICEredistFunc = 1)
67 C hActual :: HEFFITD/AREAITD
68 INTEGER k
69 _RL ridgingModeNorm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 _RL partFunc (1-OLx:sNx+OLx,1-OLy:sNy+OLy,0:nITD)
71 _RL hrMin (1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:nITD)
72 _RL hrMax (1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:nITD)
73 _RL hrExp (1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:nITD)
74 _RL ridgeRatio (1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:nITD)
75 _RL hActual (1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:nITD)
76 #endif /* SEAICE_ITD */
77 #ifdef SEAICE_CGRID
78 C compute tensile strength
79 _RL recip_tensilDepth
80 #endif /* SEAICE_CGRID */
81 CEOP
82
83 C loop boundaries
84 iMin=1-OLx
85 iMax=sNx+OLx
86 jMin=1-OLy
87 jMax=sNy+OLy
88
89 #ifdef SEAICE_ITD
90 C compute the fraction of open water as early as possible, i.e.
91 C before advection, but also before it is used in calculating the ice
92 C strength according to Rothrock (1975), hidden in S/R seaice_repare_ridging
93 DO j=jMin,jMax
94 DO i=iMin,iMax
95 opnWtrFrac(i,j,bi,bj) = 1. _d 0 - AREA(i,j,bi,bj)
96 ENDDO
97 ENDDO
98
99 IF ( useHibler79IceStrength ) THEN
100 #else
101 IF ( .TRUE. ) THEN
102 #endif /* SEAICE_ITD */
103 DO j=jMin,jMax
104 DO i=iMin,iMax
105 C-- now set up ice pressure and viscosities
106 IF ( (HEFF(i,j,bi,bj).LE.SEAICEpresH0).AND.
107 & (SEAICEpresPow0.NE.1) ) THEN
108 tmpscal1=MAX(HEFF(i,j,bi,bj)/SEAICEpresH0,ZERO)
109 tmpscal2=SEAICEpresH0*(tmpscal1**SEAICEpresPow0)
110 ELSEIF ( (HEFF(i,j,bi,bj).GT.SEAICEpresH0).AND.
111 & (SEAICEpresPow1.NE.1) ) THEN
112 tmpscal1=MAX(HEFF(i,j,bi,bj)/SEAICEpresH0,ZERO)
113 tmpscal2=SEAICEpresH0*(tmpscal1**SEAICEpresPow1)
114 ELSE
115 tmpscal2=HEFF(i,j,bi,bj)
116 ENDIF
117 PRESS0(I,J,bi,bj)=SEAICE_strength*tmpscal2
118 & *EXP(-SEAICE_cStar*(SEAICE_area_max-AREA(i,j,bi,bj)))
119 ZMAX(I,J,bi,bj) = SEAICE_zetaMaxFac*PRESS0(I,J,bi,bj)
120 ZMIN(I,J,bi,bj) = SEAICE_zetaMin
121 PRESS0(I,J,bi,bj)= PRESS0(I,J,bi,bj)*HEFFM(I,J,bi,bj)
122 ENDDO
123 ENDDO
124 #ifdef SEAICE_ITD
125 ELSE
126 C not useHiber79IceStrength
127 DO j=jMin,jMax
128 DO i=iMin,iMax
129 PRESS0(i,j,bi,bj) = 0. _d 0
130 ENDDO
131 ENDDO
132 CALL SEAICE_PREPARE_RIDGING(
133 O hActual,
134 O hrMin, hrMax, hrExp, ridgeRatio, ridgingModeNorm, partFunc,
135 I iMin, iMax, jMin, jMax, bi, bj, myTime, myIter, myThid )
136 IF ( SEAICEredistFunc .EQ. 0 ) THEN
137 tmpscal1 = 1. _d 0 / 3. _d 0
138 DO k = 1, nITD
139 DO j=jMin,jMax
140 DO i=iMin,iMax
141 C replace (hrMax**3-hrMin**3)/(hrMax-hrMin) by identical
142 C hrMax**2+hrMin**2 + hrMax*hrMin to avoid division by potentially
143 C small number
144 IF ( partFunc(i,j,k) .GT. 0. _d 0 )
145 & PRESS0(i,j,bi,bj) = PRESS0(i,j,bi,bj)
146 & + partFunc(i,j,k) * ( - hActual(i,j,k)**2
147 & + ( hrMax(i,j,k)**2 + hrMin(i,j,k)**2
148 & + hrMax(i,j,k)*hrMin(i,j,k) )*tmpscal1
149 & / ridgeRatio(i,j,k) )
150 ENDDO
151 ENDDO
152 ENDDO
153 ELSEIF ( SEAICEredistFunc .EQ. 1 ) THEN
154 DO k = 1, nITD
155 DO j=jMin,jMax
156 DO i=iMin,iMax
157 PRESS0(i,j,bi,bj) = PRESS0(i,j,bi,bj)
158 & + partFunc(i,j,k) * ( - hActual(i,j,k)**2 +
159 & ( hrMin(i,j,k)*hrMin(i,j,k)
160 & + 2. _d 0 * hrMin(i,j,k)*hrExp(i,j,k)
161 & + 2. _d 0 * hrExp(i,j,k)*hrExp(i,j,k)
162 & )/ridgeRatio(i,j,k) )
163 ENDDO
164 ENDDO
165 ENDDO
166 ENDIF
167 C
168 tmpscal1 = SEAICE_cf*0.5*gravity*(rhoConst-SEAICE_rhoIce)
169 & * SEAICE_rhoIce/rhoConst
170 DO j=jMin,jMax
171 DO i=iMin,iMax
172 PRESS0(i,j,bi,bj) = PRESS0(i,j,bi,bj)/ridgingModeNorm(i,j)
173 & *tmpscal1
174 ZMAX(I,J,bi,bj) = SEAICE_zetaMaxFac*PRESS0(I,J,bi,bj)
175 ZMIN(I,J,bi,bj) = SEAICE_zetaMin
176 PRESS0(I,J,bi,bj)= PRESS0(I,J,bi,bj)*HEFFM(I,J,bi,bj)
177 ENDDO
178 ENDDO
179 #endif /* SEAICE_ITD */
180 ENDIF
181
182 #ifdef SEAICE_CGRID
183 C compute tensile strength
184 IF ( SEAICE_tensilFac .NE. 0. _d 0 ) THEN
185 recip_tensilDepth = 0. _d 0
186 IF ( SEAICE_tensilDepth .GT. 0. _d 0 )
187 & recip_tensilDepth = 1. _d 0 / SEAICE_tensilDepth
188 DO j=jMin,jMax
189 DO i=iMin,iMax
190 tensileStrength(i,j,bi,bj)=PRESS0(I,J,bi,bj)*SEAICE_tensilFac
191 & *exp(-ABS(R_low(I,J,bi,bj))*recip_tensilDepth)
192 ENDDO
193 ENDDO
194 ENDIF
195 #endif /* SEAICE_CGRID */
196
197 RETURN
198 END

  ViewVC Help
Powered by ViewVC 1.1.22