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

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

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


Revision 1.6 - (show annotations) (download)
Tue Oct 20 22:42:23 2015 UTC (8 years, 6 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, HEAD
Changes since 1.5: +32 -1 lines
print out square-sum velocity for ECSE project, only activated with a CPP command, will not affect anything else

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_timestep.F,v 1.5 2015/03/23 14:07:16 dgoldberg Exp $
2 C $Name: $
3
4 #include "STREAMICE_OPTIONS.h"
5 #ifdef ALLOW_AUTODIFF
6 # include "AUTODIFF_OPTIONS.h"
7 #endif
8
9 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
10
11 CBOP
12 SUBROUTINE STREAMICE_TIMESTEP ( myThid, myIter,
13 & iLoop, myTime )
14
15 C /============================================================\
16 C | SUBROUTINE |
17 C | o |
18 C |============================================================|
19 C | |
20 C \============================================================/
21 IMPLICIT NONE
22
23 C === Global variables ===
24 #include "SIZE.h"
25 #include "GRID.h"
26 #include "EEPARAMS.h"
27 #include "PARAMS.h"
28 #include "STREAMICE.h"
29 #ifdef ALLOW_AUTODIFF
30 # include "STREAMICE_ADV.h"
31 # include "STREAMICE_BDRY.h"
32 # include "STREAMICE_CG.h"
33 #endif
34 #ifdef ALLOW_AUTODIFF_TAMC
35 # include "tamc.h"
36 #endif
37
38 INTEGER myThid, myIter, iLoop
39 _RL myTime
40 LOGICAL DIFFERENT_MULTIPLE
41 EXTERNAL DIFFERENT_MULTIPLE
42
43 #ifdef ALLOW_STREAMICE
44
45 INTEGER i, j, bi, bj, ki, kj
46 ! _RL Iratio, Imin_ratio, time_step_remain, local_u_max
47 ! _RL ratio, min_ratio
48 ! _RL local_v_max, time_step_int, min_time_step
49 CHARACTER*(MAX_LEN_MBUF) msgBuf
50 LOGICAL do_vel, tmp_residcheck, tmp_fpcheck
51 _RL sum_square_vel_tile (nSx,nSy)
52 _RL sum_square_vel
53
54 #ifdef ALLOW_AUTODIFF_TAMC
55 c**************************************
56 #include "streamice_ad_check_lev1_dir.h"
57 c**************************************
58 #endif
59
60 ! time_step_remain = deltaT
61 ! min_time_step = 1000.0
62 ! n_interm = 0
63
64 do_vel = .false.
65
66 #ifdef ALLOW_AUTODIFF
67
68 DO bj=myByLo(myThid),myByHi(myThid)
69 DO bi=myBxLo(myThid),myBxHi(myThid)
70 DO j=1-OLy,sNy+OLy
71 DO i=1-OLx,sNx+OLx
72 STREAMICE_ufacemask(i,j,bi,bj) = 0. _d 0
73 STREAMICE_vfacemask(i,j,bi,bj) = 0. _d 0
74 ru_old_si(i,j,bi,bj) = 0. _d 0
75 rv_old_si(i,j,bi,bj) = 0. _d 0
76 zu_old_si(i,j,bi,bj) = 0. _d 0
77 zv_old_si(i,j,bi,bj) = 0. _d 0
78 ! h_after_uflux_si(i,j,bi,bj) = 0. _d 0
79 #ifdef STREAMICE_HYBRID_STRESS
80 streamice_taubx (i,j,bi,bj) = 0. _d 0
81 streamice_tauby (i,j,bi,bj) = 0. _d 0
82 #endif
83 ENDDO
84 ENDDO
85 ENDDO
86 ENDDO
87
88 #endif /* ALLOW_AUTODIFF */
89
90 CALL TIMER_START('STREAMICE_TIMESTEP [FORWARD_STEP]',
91 & myThid)
92
93 WRITE(msgBuf,'(A,I10.10,E9.2,A)')
94 & 'streamice solo_time_step: nIter',
95 & myIter, myTime/86400.0/365.0, 'seconds'
96 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
97 & SQUEEZE_RIGHT , 1)
98
99 CALL STREAMICE_DUMP( mytime, myiter, myThid )
100
101 ! NEW DIRECTIVES - DNG
102 !#ifdef ALLOW_AUTODIFF_TAMC
103 !CADJ STORE float_frac_streamice = comlev1, key = ikey_dynamics,
104 !CADJ & kind = isbyte
105 !CADJ STORE surf_el_streamice = comlev1, key = ikey_dynamics,
106 !CADJ & kind = isbyte
107 !CADJ STORE base_el_streamice = comlev1, key = ikey_dynamics,
108 !CADJ & kind = isbyte
109 !#endif
110 ! NEW DIRECTIVES - DNG
111
112
113
114 do_vel = DIFFERENT_MULTIPLE( streamice_vel_update,
115 & myTime, deltaT )
116
117 if (myIter.eq.0) then
118 CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
119 CALL WRITE_FLD_XY_RL
120 & ("surf_el_init","",surf_el_streamice,0,myThid)
121 endif
122
123 CALL STREAMICE_VELMASK_UPD (myThid)
124
125
126
127 #ifdef ALLOW_STREAMICE_TIMEDEP_FORCING
128 CALL STREAMICE_FIELDS_LOAD( myTime, myIter, myThid )
129 #endif
130
131
132 #if (defined (ALLOW_STREAMICE_OAD_FP))
133
134 CALL STREAMICE_VEL_SOLVE_OPENAD ( myThid,
135 & streamice_max_nl_iter,
136 & streamice_max_cg_iter,
137 & myiter )
138
139 #else
140
141 if (streamice_maxnliter_cpl.eq.0 .OR. myIter.eq.0) then
142
143
144 CALL STREAMICE_VEL_SOLVE( myThid,
145 & streamice_max_nl_iter,
146 & streamice_max_cg_iter,
147 & myiter )
148
149 #ifdef STREAMICE_ECSECRYO_DOSUM
150
151 DO bj = myByLo(myThid), myByHi(myThid)
152 DO bi = myBxLo(myThid), myBxHi(myThid)
153 sum_square_vel_tile (bi,bj) = 0. _d 0
154 DO j=1-OLy,sNy+OLy
155 DO i=1-OLx,sNx+OLx
156 if (streamice_hmask(i,j,bi,bj).eq.1) then
157 sum_square_vel_tile (bi,bj) =
158 & sum_square_vel_tile (bi,bj) +
159 & U_streamice(i,j,bi,bj)**2 +
160 & V_streamice(i,j,bi,bj)**2
161 endif
162 ENDDO
163 ENDDO
164 ENDDO
165 ENDDO
166
167 CALL GLOBAL_SUM_TILE_RL(
168 & sum_square_vel_tile, sum_square_vel, myThid )
169 WRITE(msgBuf,'(A,I3,A,1PE22.14)') 'ECSE_CRYO_SUM ', myIter, ', ',
170 & sum_square_vel
171 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
172 & SQUEEZE_RIGHT , 1)
173
174 #endif
175
176
177 elseif (do_vel) then
178
179 CALL STREAMICE_VEL_SOLVE( myThid,
180 & streamice_maxnliter_cpl,
181 & streamice_maxcgiter_cpl,
182 & myiter )
183 endif
184
185
186
187 #endif
188
189 if(.not.STREAMICE_diagnostic_only) THEN
190
191 CALL STREAMICE_ADVECT_THICKNESS ( myThid, myIter, deltaT )
192
193 endif
194
195 ! CALL AT END INSTEAD OF BEGINNING - DNG
196 CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
197 ! print *, "GOT HERE TIMESTEP ", H_streamice(1,50,1,1)
198 ! call write_fld_xy_rl("h_got_here","",H_streamice,0,mythid)
199 ! call write_fld_xy_rl("u_got_here","",U_streamice,0,mythid)
200 ! call write_fld_xy_rl("v_got_here","",V_streamice,0,mythid)
201
202 CALL TIMER_STOP('STREAMICE_TIMESTEP [FORWARD_STEP]',
203 & myThid)
204
205 #endif
206 RETURN
207 END

  ViewVC Help
Powered by ViewVC 1.1.22