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

Contents of /MITgcm_contrib/dgoldberg/streamice/streamice_solo_timestep.F

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


Revision 1.5 - (show annotations) (download)
Tue Sep 18 17:06:48 2012 UTC (12 years, 10 months ago) by dgoldberg
Branch: MAIN
Changes since 1.4: +6 -2 lines
changes for periodic boundary conds and hybrid stress balance

1 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_solo_timestep.F,v 1.4 2012/07/27 21:07:13 heimbach 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_SOLO_TIMESTEP ( myThid, myIter,
10 & iLoop, myTime )
11
12 C /============================================================\
13 C | SUBROUTINE |
14 C | o |
15 C |============================================================|
16 C | |
17 C \============================================================/
18 IMPLICIT NONE
19
20 C === Global variables ===
21 #include "SIZE.h"
22 #include "GRID.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "STREAMICE.h"
26 #ifdef ALLOW_AUTODIFF_TAMC
27 # include "tamc.h"
28 # include "STREAMICE_ADV.h"
29 # include "STREAMICE_BDRY.h"
30 # include "STREAMICE_CG.h"
31 #endif
32
33
34 INTEGER myThid, myIter, iLoop
35 _RL myTime
36
37
38 #ifdef ALLOW_STREAMICE
39
40 INTEGER i, j, bi, bj, ki, kj
41 ! _RL Iratio, Imin_ratio, time_step_remain, local_u_max
42 ! _RL ratio, min_ratio
43 ! _RL local_v_max, time_step_int, min_time_step
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45 ! LOGICAL modelEnd
46
47 #ifdef ALLOW_AUTODIFF_TAMC
48 c**************************************
49 #include "streamice_ad_check_lev1_dir.h"
50 c**************************************
51 #endif
52
53 ! time_step_remain = deltaT
54 ! min_time_step = 1000.0
55 ! n_interm = 0
56
57 #ifdef ALLOW_AUTODIFF_TAMC
58
59 DO bj=myByLo(myThid),myByHi(myThid)
60 DO bi=myBxLo(myThid),myBxHi(myThid)
61 DO j=1-OLy,sNy+OLy
62 DO i=1-OLx,sNx+OLx
63 STREAMICE_ufacemask(i,j,bi,bj) = 0. _d 0
64 STREAMICE_vfacemask(i,j,bi,bj) = 0. _d 0
65 ru_old_si(i,j,bi,bj) = 0. _d 0
66 rv_old_si(i,j,bi,bj) = 0. _d 0
67 zu_old_si(i,j,bi,bj) = 0. _d 0
68 zv_old_si(i,j,bi,bj) = 0. _d 0
69 h_after_uflux_si(i,j,bi,bj) = 0. _d 0
70 ENDDO
71 ENDDO
72 ENDDO
73 ENDDO
74
75 #endif
76
77
78 ! do while (time_step_remain .gt. 0. _d 0)
79 !
80 ! n_interm = n_interm + 1
81 ! Imin_ratio = 1.0e-16
82 !
83 ! DO bj = myByLo(myThid), myByHi(myThid)
84 ! DO bi = myBxLo(myThid), myBxHi(myThid)
85 ! DO j=1,sNy
86 ! DO i=1,sNx
87 !
88 ! local_u_max = 0
89 ! local_v_max = 0
90 !
91 ! if (STREAMICE_hmask (i,j,bi,bj) .eq. 1.0) then
92 ! do ki = 0,1
93 ! do kj = 0,1
94 ! local_u_max =
95 ! & max (local_u_max, abs(U_streamice(i+ki,j+kj,bi,bj)))
96 ! local_v_max =
97 ! & max (local_v_max, abs(V_streamice(i+ki,j+kj,bi,bj)))
98 ! enddo
99 ! enddo
100 !
101 ! Iratio = max (local_u_max/dxF(i,j,bi,bj) ,
102 ! & local_v_max/dyF(i,j,bi,bj))
103 ! Imin_ratio = max (Imin_ratio, Iratio)
104 ! endif
105 !
106 ! enddo
107 ! enddo
108 ! enddo
109 ! enddo
110 !
111 ! CALL GLOBAL_MAX_R8 (Imin_ratio, myThid)
112 ! min_ratio = 1./(Imin_ratio+1.e-12)
113 ! time_step_int =
114 ! & min(streamice_CFL_factor*min_ratio*(365*86400),
115 ! & deltaT)
116 !
117 ! if (time_step_int .lt. min_time_step) then
118 ! WRITE(msgBuf,'(A,A,E9.2)') 'streamice solo_time_step:',
119 ! & ' abnormally small timestep ',
120 ! & streamice_CFL_factor*min_ratio*(365*86400)
121 ! CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
122 ! & SQUEEZE_RIGHT , 1)
123 ! endif
124 !
125 ! if (time_step_int .ge. time_step_remain) then
126 ! time_step_int = time_step_remain
127 ! time_step_remain = 0.0
128 ! else
129 ! time_step_remain = time_step_remain - time_step_int
130 ! endif
131
132
133
134
135
136
137 ! if (time_step_int .gt. 1000) then
138
139 WRITE(msgBuf,'(A,I10.10,E9.2,A)')
140 & 'streamice solo_time_step: nIter',
141 & myIter, myTime/86400.0/365.0, 'seconds'
142 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
143 & SQUEEZE_RIGHT , 1)
144
145 CALL STREAMICE_DUMP( mytime, myiter, myThid )
146
147 CALL STREAMICE_VELMASK_UPD (myThid)
148 CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
149 CALL STREAMICE_VEL_SOLVE( myThid )
150 ! endif
151
152
153 if(.not.STREAMICE_diagnostic_only) THEN
154
155 CALL STREAMICE_ADVECT_THICKNESS ( myThid, deltaT )
156
157 endif
158
159
160 ! enddo
161
162 ! CALL STREAMICE_VELMASK_UPD (myThid)
163 ! CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
164 ! CALL STREAMICE_VEL_SOLVE( myThid )
165
166 ! modelEnd = myTime.EQ.endTime .OR. myIter.EQ.nEndIter
167
168 ! #ifdef ALLOW_DIAGNOSTICS
169 !
170 ! ! this stuff was to replace what is in forward_step, but not
171 ! ! forward_step will be called
172 !
173 ! ! IF ( useDiagnostics ) THEN
174 ! ! CALL DIAGNOSTICS_SWITCH_ONOFF( myTime, myiter, myThid )
175 ! ! ! C-- State-variables diagnostics
176 ! ! ! CALL TIMER_START('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
177 ! ! ! CALL DO_STATEVARS_DIAGS( myTime, 0, myIter, myThid )
178 ! ! ! CALL TIMER_STOP ('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
179 ! ! ENDIF
180 !
181 !
182 ! IF ( useDiagnostics ) THEN
183 ! CALL DIAGNOSTICS_FILL(U_streamice,'SI_Uvel ',
184 ! & 0,1,0,1,1,myThid)
185 ! CALL DIAGNOSTICS_FILL(V_streamice,'SI_Vvel ',
186 ! & 0,1,0,1,1,myThid)
187 ! CALL DIAGNOSTICS_FILL(H_streamice,'SI_Thick',
188 ! & 0,1,0,1,1,myThid)
189 ! CALL DIAGNOSTICS_FILL(area_shelf_streamice,'SI_area ',
190 ! & 0,1,0,1,1,myThid)
191 ! CALL DIAGNOSTICS_FILL(float_frac_streamice,'SI_float',
192 ! & 0,1,0,1,1,myThid)
193 !
194 ! ENDIF
195 !
196 ! ! IF ( useDiagnostics ) THEN
197 ! ! CALL TIMER_START('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
198 ! ! CALL DO_STATEVARS_DIAGS( myTime, 2, myIter, myThid )
199 ! ! CALL TIMER_STOP ('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
200 ! ! ENDIF
201 !
202 ! #endif /* ALLOW_DIAGNOSTICS */
203
204 ! myIter = nIter0 + iLoop
205 ! myTime = startTime + deltaTClock * float(iLoop)
206 !
207 ! CALL TIMER_START('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
208 ! CALL DO_THE_MODEL_IO( modelEnd, myTime, myIter, myThid )
209 ! CALL TIMER_STOP ('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
210
211
212 #endif
213 RETURN
214 END

  ViewVC Help
Powered by ViewVC 1.1.22