/[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.7 - (show annotations) (download)
Thu Sep 27 20:29:01 2012 UTC (12 years, 10 months ago) by dgoldberg
Branch: MAIN
Changes since 1.6: +3 -1 lines
various changes

1 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_solo_timestep.F,v 1.6 2012/09/20 02:04:45 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 #ifdef STREAMICE_HYBRID_STRESS
71 streamice_taubx (i,j,bi,bj) = 0. _d 0
72 streamice_tauby (i,j,bi,bj) = 0. _d 0
73 #endif
74 ENDDO
75 ENDDO
76 ENDDO
77 ENDDO
78
79 #endif
80
81
82 ! do while (time_step_remain .gt. 0. _d 0)
83 !
84 ! n_interm = n_interm + 1
85 ! Imin_ratio = 1.0e-16
86 !
87 ! DO bj = myByLo(myThid), myByHi(myThid)
88 ! DO bi = myBxLo(myThid), myBxHi(myThid)
89 ! DO j=1,sNy
90 ! DO i=1,sNx
91 !
92 ! local_u_max = 0
93 ! local_v_max = 0
94 !
95 ! if (STREAMICE_hmask (i,j,bi,bj) .eq. 1.0) then
96 ! do ki = 0,1
97 ! do kj = 0,1
98 ! local_u_max =
99 ! & max (local_u_max, abs(U_streamice(i+ki,j+kj,bi,bj)))
100 ! local_v_max =
101 ! & max (local_v_max, abs(V_streamice(i+ki,j+kj,bi,bj)))
102 ! enddo
103 ! enddo
104 !
105 ! Iratio = max (local_u_max/dxF(i,j,bi,bj) ,
106 ! & local_v_max/dyF(i,j,bi,bj))
107 ! Imin_ratio = max (Imin_ratio, Iratio)
108 ! endif
109 !
110 ! enddo
111 ! enddo
112 ! enddo
113 ! enddo
114 !
115 ! CALL GLOBAL_MAX_R8 (Imin_ratio, myThid)
116 ! min_ratio = 1./(Imin_ratio+1.e-12)
117 ! time_step_int =
118 ! & min(streamice_CFL_factor*min_ratio*(365*86400),
119 ! & deltaT)
120 !
121 ! if (time_step_int .lt. min_time_step) then
122 ! WRITE(msgBuf,'(A,A,E9.2)') 'streamice solo_time_step:',
123 ! & ' abnormally small timestep ',
124 ! & streamice_CFL_factor*min_ratio*(365*86400)
125 ! CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
126 ! & SQUEEZE_RIGHT , 1)
127 ! endif
128 !
129 ! if (time_step_int .ge. time_step_remain) then
130 ! time_step_int = time_step_remain
131 ! time_step_remain = 0.0
132 ! else
133 ! time_step_remain = time_step_remain - time_step_int
134 ! endif
135
136
137
138
139
140
141 ! if (time_step_int .gt. 1000) then
142
143 WRITE(msgBuf,'(A,I10.10,E9.2,A)')
144 & 'streamice solo_time_step: nIter',
145 & myIter, myTime/86400.0/365.0, 'seconds'
146 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
147 & SQUEEZE_RIGHT , 1)
148
149 CALL STREAMICE_DUMP( mytime, myiter, myThid )
150
151
152
153 CALL STREAMICE_VELMASK_UPD (myThid)
154 CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
155 CALL STREAMICE_VEL_SOLVE( myThid )
156 ! endif
157
158
159 if(.not.STREAMICE_diagnostic_only) THEN
160
161 CALL STREAMICE_ADVECT_THICKNESS ( myThid, deltaT )
162
163 endif
164
165
166 ! enddo
167
168 ! CALL STREAMICE_VELMASK_UPD (myThid)
169 ! CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
170 ! CALL STREAMICE_VEL_SOLVE( myThid )
171
172 ! modelEnd = myTime.EQ.endTime .OR. myIter.EQ.nEndIter
173
174 ! #ifdef ALLOW_DIAGNOSTICS
175 !
176 ! ! this stuff was to replace what is in forward_step, but not
177 ! ! forward_step will be called
178 !
179 ! ! IF ( useDiagnostics ) THEN
180 ! ! CALL DIAGNOSTICS_SWITCH_ONOFF( myTime, myiter, myThid )
181 ! ! ! C-- State-variables diagnostics
182 ! ! ! CALL TIMER_START('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
183 ! ! ! CALL DO_STATEVARS_DIAGS( myTime, 0, myIter, myThid )
184 ! ! ! CALL TIMER_STOP ('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
185 ! ! ENDIF
186 !
187 !
188 ! IF ( useDiagnostics ) THEN
189 ! CALL DIAGNOSTICS_FILL(U_streamice,'SI_Uvel ',
190 ! & 0,1,0,1,1,myThid)
191 ! CALL DIAGNOSTICS_FILL(V_streamice,'SI_Vvel ',
192 ! & 0,1,0,1,1,myThid)
193 ! CALL DIAGNOSTICS_FILL(H_streamice,'SI_Thick',
194 ! & 0,1,0,1,1,myThid)
195 ! CALL DIAGNOSTICS_FILL(area_shelf_streamice,'SI_area ',
196 ! & 0,1,0,1,1,myThid)
197 ! CALL DIAGNOSTICS_FILL(float_frac_streamice,'SI_float',
198 ! & 0,1,0,1,1,myThid)
199 !
200 ! ENDIF
201 !
202 ! ! IF ( useDiagnostics ) THEN
203 ! ! CALL TIMER_START('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
204 ! ! CALL DO_STATEVARS_DIAGS( myTime, 2, myIter, myThid )
205 ! ! CALL TIMER_STOP ('DO_STATEVARS_DIAGS [FORWARD_STEP]',myThid)
206 ! ! ENDIF
207 !
208 ! #endif /* ALLOW_DIAGNOSTICS */
209
210 ! myIter = nIter0 + iLoop
211 ! myTime = startTime + deltaTClock * float(iLoop)
212 !
213 ! CALL TIMER_START('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
214 ! CALL DO_THE_MODEL_IO( modelEnd, myTime, myIter, myThid )
215 ! CALL TIMER_STOP ('DO_THE_MODEL_IO [FORWARD_STEP]',myThid)
216
217
218 #endif
219 RETURN
220 END

  ViewVC Help
Powered by ViewVC 1.1.22