source: branches/iLoveclim/SOURCES/steps_time_loop_avec_iterbeta.f90 @ 187

Last change on this file since 187 was 187, checked in by aquiquet, 6 years ago

Grisli-iloveclim branch merged to trunk at revision 185

File size: 13.6 KB
Line 
1!> \file steps_time_loop.f90
2!! TOOOOOOOOO DOOOOOOOOOOOOO
3!! Step_grisli contient
4!<
5
6!--------------------------------------------------------------------------
7! step_time_loop est a l'interieur de la boucle temps.
8! il commence par icethick, qui détermine dt, isynchro
9
10! ensuite contient les appels aux diverses sorties
11! puis un appel a step_grisli
12
13
14subroutine step_time_loop       
15
16  use module3d_phy
17  use module_choix ! module de choix du type de run
18                   !  module_choix donne acces a tous les modules
19                   !  de declaration des packages
20  use icetempmod
21  use sorties_ncdf_grisli
22  use flottab_mod
23  use diagno_mod
24  use bilan_eau_mod
25!  use track_debug
26
27
28  implicit none
29  integer :: nt_init = 0      ! number of loops for initialisation of ice thickness
30
31  if (itracebug.eq.1)  call tracebug('Entree dans step_time_loop ')
32  if (itracebug.eq.1) write(num_tracebug,*) 'nt = ',nt,'  iter_beta = ',iter_beta
33
34
35  ! ice thickness evolution
36  !=============================
37
38
39  spinup_icethick: if ((ispinup.eq.0.or.ispinup.eq.2.or.nt.lt.nt_init) &
40       .and.(iter_beta.eq.0)) then 
41
42     !-------------------------------------------------------------------
43     ! spinup_icethick : Le calcul changement d'epaisseur (icethick)
44     !----------------
45     !   - est fait dans tous les cas pour les premieres boucles temporelles
46     !   - pour ispinup = 0 (run standard) sauf si iter_beta = 0
47     !   - pour ispinup = 2 (force avec vitesses de bilan)
48     !
49     ! else
50     !   juste un increment pour le temps
51     !    -  pour ispinup = 1 et  ispinup = 3  temperature calculation
52     
53     !-------------------------------------------------------------------
54
55     if (itracebug.eq.1)  call tracebug(' Dans spinup_icethick : appelle icethick')
56
57     call icethick3
58     call flottab
59     call determin_tache
60     call calving
61     call ablation_bord
62     call bilan_eau
63     call bilan_flux_output
64     call flottab
65     if (isynchro.eq.1.or.nt.eq.1) call determin_marais
66     if (itracebug.eq.1)  call tracebug('apres marais')
67
68     ! new calculation of ice surface elevation
69     where(.not.flot(:,:))
70        S(:,:)=Bsoc(:,:)+H(:,:)
71        S(:,:)=max(S(:,:),sealevel)
72        B(:,:)=Bsoc(:,:)
73     end where
74     
75     ! calcul de Hmx et Hmy -> shift=-1, dim=1 -> H(i-1,j)
76
77     hmx(:,:)=0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=1))
78     hmy(:,:)=0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=2))
79     hmx(1,:)=0.
80     hmy(:,1)=0.
81
82     ! mise a 0 des vitesses quand epaisseur nulle
83     where (hmx(:,:).le.1.)
84        uxbar(:,:)=0.
85     endwhere
86     where (hmy(:,:).le.1.)
87        uybar(:,:)=0.
88     endwhere
89
90  else   ! time increment when no icethick : ispinup= 1 or 3    ! loop spinup_icethick
91
92     hdot(:,:)=0.
93     time=nt*dtmax
94
95     if (itracebug.eq.1) write(num_tracebug,*) ' Dans spinup_icethick:  no icethick ',ispinup, &
96          '    time=',time
97
98
99  end if spinup_icethick
100  ! end of ice thickness evolution
101  !====================================================================
102
103
104
105  ! outputs
106  !====================================================================
107
108  !   vertical plan snapshots (profiles)
109  !------------------------------------------------------------------
110
111  !if ((NT.eq.1) &    !   .or.(NT.eq.2)
112  !     .or.(mod(abs(dble(TIME)),dble(DTPROFILE)).lt.dble(dtmin)) &
113  !     .or.(abs(TIME-TEND).lt.dtmin)) then
114  !  call sortieprofile()
115  !endif
116
117  !  sorties netcdf Hassine (aout 2010)  (2D and 3D)
118  !------------------------------------------------------------------
119
120  call testsort_time_ncdf(time)
121  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
122  if (isynchro.eq.1) then
123    call shortoutput
124    diff_H = 0.
125    Bm_dtt(:,:) = 0.
126    bmelt_dtt(:,:) = 0.
127    calv_dtt(:,:)=0.
128    ablbord_dtt(:,:)=0.
129    diff_H_2D(:,:)=0.
130    grline_dtt(:,:)=0.
131  endif
132
133  !   sortie compteur tous les dtcpt ans
134  !------------------------------------------------------------------
135  !iout == 1 sortie cptr
136  !iout == 2 sortie nc
137  if (itracebug.eq.1)  call tracebug('dans steps_time_loop avant call out_recovery ')
138
139  call out_recovery(iout)
140
141  ! end of outputs
142
143  !====================================================================
144  !
145  call step_thermomeca()
146  !
147  ! contient tout le reste de la dynamique et du forçage
148  !====================================================================
149
150end subroutine step_time_loop
151
152
153
154
155
156
157!---------------------------------------------------------------------
158! The subroutine  step_thermomeca() calls the following processes
159!
160! - climatic forcing and its impact on surface mass balance
161! - dynamic velocities (SIA)
162! - ice temperature
163
164subroutine step_thermomeca()
165
166
167  use module3d_phy
168  use module_choix ! module de choix du type de run
169  !  module_choix donne acces a tous les modules
170  !  de declaration des packages
171  use icetempmod
172  use sorties_ncdf_grisli
173  use flottab_mod
174  use diagno_mod
175  use resolmeca_SIA_L1
176!  use track_debug
177
178
179  implicit none
180
181  integer :: m
182  logical :: shelf_vitbil = .true.   ! si vrai on prend les vitesses de bilan pour le shelf
183  integer :: nt_init_tm = 0          ! number of loops for initialisation of thermo mechanical
184  integer :: iter_visco              ! number of iterations for ssa viscosity
185
186  if (ispinup.le.1) shelf_vitbil = .false.         ! general case, ice shelves velocities are computed by diagnoshelf
187
188  timemax=time
189  if (itracebug.eq.1) write(num_tracebug,*) 'entree dans step_thermomeca', &
190       '   nt=',nt,'iter_beta=',iter_beta
191
192  !--------------------------------------------------------------------
193  !     lecture dans un petit fichier "runname.limit" au cas ou les
194  !     parametres du run seraient changes 
195  !                                                   
196  !--------------------------------------------------------------------
197
198!  call limit_file(nt,real(time),dt,tend,dtsortie,dtcpt,testdiag,dtt,runname)
199
200  !if (time.lt.tgrounded) then
201  !   marine=.false.
202  !else
203  marine=.true.
204  !endif
205
206  ! update the regions (floating, ice ...)
207  !-------------------------------------------
208  call masque()
209
210  if (iter_beta.gt.0)   call init_dragging
211
212
213  !-----------------------------------------------------------------------!
214  !   debut d'un bloc appels tous les dtt (pas de temps long- asynchrone) !
215  !-------------   -------------------------------------------------------!
216
217
218
219  isync_1: if (ISYNCHRO.eq.1) then          ! debut bloc appels tous les dtt   
220
221
222     ! climatic forcing
223     !=====================
224     call forclim                             
225     call ablation
226
227
228
229     ! SIA dynamic velocities  (deformation + loi de glissement )
230     !========================
231
232     ! remark : velocity is 3D
233     !          to update the velocity for ice temperature calculation
234     !            - surface mass balance for velocity (because ablation was called)
235     !            - impact of surface slope
236
237
238     spinup_1_veloc: if ((ispinup.ne.2).or.(nt.lt.nt_init_tm)) then        ! cas general
239
240        !---------------------------------------------------------------------------------
241        ! spinup_1 : calcul des vitesses dynamiques :
242        !------------
243        !            - est fait dans tous les cas pour les premieres boucles temporelles
244        !            - est fait pour ispinup=3 pour calibration forme de vitesse
245        !            - n'est pas fait pour ispinup=2 (test balance vel sur icethick)
246        !
247        !---------------------------------------------------------------------------------
248
249        if (itracebug.eq.1)  call tracebug(' Dans spinup_1_veloc : calculer SIA_velocities')
250
251        call Neffect()                                             
252        call SIA_velocities()
253
254     else    ! ispinup = 2
255
256        call force_balance_vel   ! fait l'ensemble du champ (flgz ou pas)
257
258     endif spinup_1_veloc
259
260
261     ! ice temperature
262     !===================================================================
263
264     ! update values in the structures Geom_g, Temperature_g, ...
265
266!afq     calc_temp:     if ((nt.gt.2).and.(geoplace(1:5).ne.'mism3')) then
267     calc_temp:     if (geoplace(1:5).ne.'mism3') then
268        if (itracebug.eq.1)  call tracebug('avant appel icetemp')
269        call icetemp
270        ! subroutines pour le calcul de la fusion basale
271        call bmeltshelf
272        call bmelt_grounded
273
274     endif calc_temp
275
276
277     ! flowlaw
278     !===================================================================
279
280     spinup_2_flowlaw: if ((ispinup.ne.2).or.(nt.lt.nt_init_tm)) then    ! cas general
281
282        !---------------------------------------------------------------------------------
283        ! spinup_2_flowlaw
284        !----------------
285        ! si ispinup =   2 , on ne fait pas le calcul de flowlaw, ni de diffusiv
286        !                    puisque les vitesses de bilan sont imposees
287        !                                             (initialisee nt < nt_init_tm)
288        !                   
289        ! Flowlaw et diffusiv : servent soit directement (ispinup = 0,1) soit pour le
290        !                       rescaling (ispinup = 3)
291        !---------------------------------------------------------------------------------
292
293        if (itracebug.eq.1)  call tracebug(' Dans spinup_2_flowlaw')
294
295           call flow_general
296           do iglen=n1poly,n2poly
297              call flowlaw(iglen)
298           end do
299
300
301     end if spinup_2_flowlaw
302
303     if (ispinup.eq.3) then
304        call calc_coef_vitbil                    ! recalibre sa_mx et s2a_mx et ddbx pour toute la zone posee
305     end if                                      ! Dans le shelf flgz = Ubar = Vbil et udef=0
306
307     call tracer      ! aurel neem (attention, position a verifier)   
308
309  endif isync_1
310
311
312  ! fin du bloc tous les dtt isync_1
313  !------------------------------------
314
315
316  spinup_4_vitdyn: if  ((ispinup.le.1).or.(nt.lt.nt_init_tm)) then 
317
318     !---------------------------------------------------------------------------------
319     ! spinup_4_vitdyn
320     !----------------
321     ! Passe dans ce bloc que quand on veut calculer les vitesses dynamiques :
322     ! - initialisations (nt.lt.nt_init_tm)
323     ! - run standard  (ispinup=0) (y compris iter_beta.ne.0)
324     ! - spinup temperature avec vitesses dynamiques  (ispinup = 1)               
325     !---------------------------------------------------------------------------------
326
327
328
329     call Neffect()
330
331     call diffusiv()
332
333
334     iterbeta:     if (iter_beta.ne.0) then          ! only for iterations on beta
335
336        if (.not.shelf_vitbil) then    !  bloc si les vitesses shelves viennent de diagnoshelf
337
338           !  Vcol declare dans le module spinup_mod
339           !  ou dans le dragging si no_spinup
340
341           where (flotmx(:,:))
342              uxbar(:,:)=uxflgz(:,:)
343           elsewhere
344              uxbar(:,:)=Vcol_x(:,:)
345           end where
346
347           where (flotmy(:,:))
348              uybar(:,:)=uyflgz(:,:)
349           elsewhere
350              uybar(:,:)=Vcol_y(:,:)
351           end where
352        else
353           uxbar(:,:)=Vcol_x(:,:)
354           uybar(:,:)=Vcol_y(:,:)
355        end if
356     end if iterbeta
357
358
359     ! strain rate calculations
360     !===========================
361
362     call strain_rate()
363
364
365     if (iter_beta.ne.0) then               ! on n'a utilise les vitesses de bilan que pour strain_rate "Dirichlet ?"
366        uxbar(:,:)=uxflgz(:,:)+uxdef(:,:)
367        uybar(:,:)=uyflgz(:,:)+uydef(:,:)
368     end if
369
370
371
372     ! ice shelves and ice streams velocities : SSA
373     !==============================================
374
375     !-----------------------------------------------------------------------
376     !              debut d'un deuxieme bloc appels tous les dtt                         
377     !-------------   -------------------------------------------------------
378
379     isync_2:    if ((shelfy).and.(marine).and.(isynchro.eq.1)) then               
380
381        !les 3 lignes ci-dessous pour avoir les champs avant diagno (en cas de pb colineaire)
382        !call init_sortie_ncdf
383        !call sortie_ncdf_cat
384
385        if (icompteur.eq.1) then    ! reprise de tout le vecteur d'etat   
386           iter_visco = 1
387
388        else if ((icompteur.ne.1).and.(nt.le.1)) then  ! initialisation avec reprise partielle
389                                                       ! ou nulle du vecteur d' etat
390          iter_visco = 10
391        else
392          iter_visco = 2
393        end if
394 
395
396           do m=1,iter_visco 
397              call diagnoshelf
398              call mix_SIA_L1 
399              call strain_rate
400           end do
401
402! iterations pour affiner beta en fonction des vitesses de bilan
403 
404           if ((time.ge.time_iter).and.(time.le.time_iter+20.)) then    !iterations seulment pendant 15 ans
405              do m=1,nb_iter_vitbil
406                 call beta_iter_vitbil 
407                 call diagnoshelf
408                 call mix_SIA_L1 
409                 call strain_rate
410              end do
411           end if
412! fin des iterations beta_iter_vitbil
413
414        endif isync_2
415
416
417     call  mix_SIA_L1 
418
419  end if spinup_4_vitdyn
420 
421  ! isostasy
422  !=================
423
424  spinup_3_bed: if ((ISYNCHRO.eq.1).and.(ispinup.eq.0.or.nt.lt.nt_init_tm)) then
425  !---------------------------------------------------------------------------------
426  ! spinup_3_bed
427  !----------------
428  ! Ne passe dans ce bloc que quand on veut l'isostasie, donc si variations epaisseur
429  ! run standard  (ispinup=0) et pour les initialisations                 
430  !---------------------------------------------------------------------------------
431
432  if (itracebug.eq.1)  call tracebug(' Dans spinup_3_bed')
433
434  if ((nbed.eq.1).and.nt.ne.1.and.isynchro.eq.1.and.(mod(abs(TIME),50.).lt.dtmin)) then
435    call bedrock                 !  bedrock adjustment
436  endif
437
438  call lake_to_slv               ! pour traiter dynamiquement les shelves sur lac
439
440  end if spinup_3_bed
441   
442
443end subroutine step_thermomeca
Note: See TracBrowser for help on using the repository browser.