source: trunk/SOURCES/main3D-0.4-40km.f90 @ 102

Last change on this file since 102 was 65, checked in by dumas, 8 years ago

Deleting unused variables and move old sources

File size: 10.2 KB
Line 
1!     **********************************************************************
2!     *       GRISLI      Grenoble Ice Shelves-Land Ice
3!     **********************************************************************
4
5
6!     Ont participe a l'ecriture de ce modele :
7!
8!                   Catherine Ritz                           (tout du long)
9!                   Adeline Fabre                      (la partie Gremlins)
10!                   Vincent Rommelaere         (ice shelves et ice streams)
11!                   Christophe Dumas (debut f90,              (Antarctique)
12!                   Vincent Peyaud      (portage HN,calving, front, hydrol)
13!                   Cyril Mazauric                                  (AGRIF)
14!                   Hassine Baya             (netcdf, doxygen, icetemp,...)
15!
16!     catritz@lgge.obs.ujf-grenoble.fr
17!
18!     **********************************************************************
19
20
21
22!> \mainpage GRISLI Modele 3D De Calotte Glaciaire
23!!
24!! \section start Pour commencer
25!! Le programme principal est dans le module main3D.
26!! Ce module est dans le fichier  main3D-0.4-40km.f90.
27!!
28!! \section tree Arbre d'appel
29!!
30!! - call grisli_init()
31!!   - step_grisli()
32!!   - sortie_ncdf_cat()
33!!   - testsort_time_ncdf()
34!!   - initial()
35!!   - sortie_hz_multi()
36!! - call step_grisli1()
37!!
38!<
39
40
41!> \file main3D-0.4-40km.f90 GRISLI Modele 3D De Calotte Glaciaire
42!! programme principal
43!! (voir l'\ref tree)
44!!
45!! @brief   modele flow line d'evolution de calotte
46!! @authors         Catherine Ritz     catritz@lgge.obs.ujf-grenoble.fr  (tout du long)
47!! @authors         Adeline Fabre                      (la partie Gremlins)
48!! @authors         Vincent Rommelaere         (ice shelves et ice streams)
49!! @authors         Christophe Dumas (debut f90,              (Antarctique)
50!! @authors         Vincent Peyaud      (portage HN,calving, front, hydrol)
51!! @authors         Cyril Mazauric                                  (AGRIF)
52!!
53!!
54!! @note use module3D_phy
55!! @note use module_choix
56!! @note use flottab_mod
57!! @note use icetempmod
58!! @note use sorties_ncdf_grisli
59!! @note use diagno_mod
60!! @note use resolmeca_SIA_L1
61!!
62!!
63!! Ce module appelle les routines suivantes :
64!! - grisli_init()
65!! - step_grisli1()
66!! - step_output()
67!!
68!<
69
70!> \namespace main3D GRISLI Modele 3D De Calotte Glaciaire
71!! programme principal
72!! (voir l'\ref tree)
73!!
74!!
75!! @brief   modele flow line d'evolution de calotte
76!! @authors         Catherine Ritz     catritz@lgge.obs.ujf-grenoble.fr  (tout du long)
77!! @authors         Adeline Fabre                      (la partie Gremlins)
78!! @authors         Vincent Rommelaere         (ice shelves et ice streams)
79!! @authors         Christophe Dumas (debut f90,              (Antarctique)
80!! @authors         Vincent Peyaud      (portage HN,calving, front, hydrol)
81!! @authors         Cyril Mazauric                                  (AGRIF)
82!!
83!!
84!! @note use module3D_phy
85!! @note use module_choix
86!! @note use flottab_mod
87!! @note use icetempmod
88!! @note use sorties_ncdf_grisli
89!! @note use diagno_mod
90!! @note use resolmeca_SIA_L1
91!!
92!!
93!! @todo itracebug : faire une routine
94!!
95!! Ce module appelle les routines suivantes :
96!! - grisli_init()
97!! - step_grisli1()
98!!
99!! Defined in file main3D-0.4-40km.f90
100!<
101
102program main3D
103
104  USE module3D_phy
105  USE module_choix !   module de choix du type de run
106  !  module_choix donne acces a tous les modules
107  !  de declaration des packages
108  use flottab_mod
109  use icetempmod
110  use sorties_ncdf_grisli
111  use diagno_mod 
112  use resolmeca_SIA_L1
113!  use track_debug
114
115  implicit none
116
117
118  ! good luck
119
120  call grisli_init  ! Initializations
121
122  time_loop: do nt=1,ntmax         !____________________________ debut boucle temporelle
123
124     if (time.ge.tend) exit
125     if (time.gt.10) itracebug = 0
126     call step_time_loop()
127
128  end do time_loop
129  if (itracebug.eq.1)  call tracebug('dans main avant call out_recovery ')
130  call out_recovery(iout)
131
132  write(6,*) "end of the run at time = ",time
133  write(6,*) "_____________________________________________________________________"
134
135end program main3D
136
137
138!---------------------------------------------------------------------------------------
139subroutine grisli_init
140
141  USE module3D_phy
142  USE module_choix ! module de choix du type de run
143  !  module_choix donne acces a tous les modules
144  !  de declaration des packages
145  use flottab_mod
146  use icetempmod
147  use sorties_ncdf_grisli
148  use util_recovery
149  use diagno_mod 
150!  use track_debug
151
152  implicit none
153
154  if (itracebug.eq.1)  call tracebug(' Entree dans routine grisli_init')
155  !      switch pour passer ou non par T lliboutry calcule => 0, ne passe pas,
156  !      1 ou 2 passe (se met a 0 tout seul si on prend un fichier .cptr)
157
158  ITEMP=0
159
160  !      switch couple physique faible =>  CP et CT independant T
161  !               0     pas de trait. vert.  A FAIRE           niveau L0
162  !               1     pas de couplage , faible physique      niveau L1
163  !               2     couplage, faible physique              niveau L2
164  !               3     couplage, physique complete sans CBT   niveau L3
165  !               4     idem 3 mais loi de def. Duval          niveau L4
166  ICOUPLE=4
167  !     switch margin IMARGIN=0 fixed, IMARGIN=1 moving
168  IMARGIN=1
169
170  TIMECG=TBEGIN
171  nt=-1   ! utilisee dans initialisation flottab
172  !     sortie profile tous les dtprofile
173  DTPROFILE=50000.
174  marine=.true.
175  !     ----------------------------------fin des modifs run les plus usuelles
176  ! DIRNAMEOUT='../RESULTATS/'
177  DIRNAMEOUT='./'
178
179  call initial  ! routine qui appel toutes les routines d'initialisation
180
181
182  !      call init_sortie_ncdf
183  !      call sortie_ncdf_cat
184  !      STOP
185
186  !     compteur tous les DTCPT
187  DTCPT=dtout
188
189  dtsortie=minval(dtsortie_hz(:))
190
191  !     ************ OPEN FILES.RITZ ****************
192
193  if ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
194     ! fichier de reference pour le niveau des mers
195     open(num_sealevel,file=TRIM(DIRNAMEOUT)//'sealevel'//runname//'.ritz',position="append")
196     open(num_ts_ritz,file=TRIM(DIRNAMEOUT)//'ts_'//runname//'.ritz',position="append")
197     open(num_ic_vo,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'vo.ritz',position="append")
198     open(num_ic_by,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'by.ritz',position="append")
199     open(num_ic_dm,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dm.ritz',position="append")
200     open(num_ic_dc,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dc.ritz',position="append")
201     open(num_ic_df,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'df.ritz',position="append")
202  endif
203
204  !------------------------------ INITIALISATION ----------------------------
205  !
206! ecriture netcdf apres initialisation
207
208
209
210  call testsort_time_ncdf(dble(tbegin))
211  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
212
213
214
215  if (iter_beta.eq.0) then
216
217     if (itracebug.eq.1)  call tracebug(' Avant appel routine icethick3')
218     call icethick3
219     debug_3D(:,:,88) = S(:,:)
220     if (itracebug.eq.1)  call tracebug(' Apres appel routine icethick3')
221  end if
222
223
224  !     Tgrounded, temps pendant lequel la calotte est terrestre
225  tgrounded=tbegin-10.
226  !if (tgrounded.le.tbegin) then
227  marine=.true. ! Cas la calotte est terrestre
228  !end if
229
230  ! test vincent car certains H(i,j)=0 dans fichier de reprise
231  do j=1,ny
232     do i=1,nx
233        H(i,j)=max(1.,H(i,j))
234     enddo
235  enddo
236
237
238  ! call firstoutput()           ! ouverture fichier temporel et premieres ecritures
239
240  call forclim                   !  initialisation BM et TS         
241  call ablation
242
243
244
245  !  -----------                  CALCULATION OF INITIAL TEMPERATURES
246
247  tcpt:if (ICOMPTEUR.eq.0) then
248
249
250     if ((GEOPLACE.ne.'eismint').and.(GEOPLACE(1:6).ne.'marine')) then
251        !       ITEMP=1 => calcul de T lliboutry; ITEMP=2 => reprise d'un fichier cptr
252        !       ITEMP=0 => on ne prend pas en compte T Lliboutry
253        !       ITEMP=3 => on prend les temperatures d'un fichier cptr
254
255
256
257        if ((ITEMP.eq.0).or.(ITEMP.eq.3)) then
258           call masque()
259
260           call Neffect()
261
262           call flottab()
263
264           call Neffect()
265
266
267           !          call vitbilan_lect   ! routine de lecture des vitesses de bilan
268           !       ========================================================
269
270           if (ITEMP.eq.0) call lineartemp()
271
272           call bmelt_grounded 
273           call  bmeltshelf
274
275
276           call flow_general
277
278           do iglen=n1poly,n2poly
279              call flowlaw(iglen)
280           end do
281
282
283           call Neffect()
284           call flottab()
285
286
287           call Neffect()
288
289
290           call diffusiv()
291           call SIA_velocities()
292
293        endif
294
295
296     endif
297     !     fin du test geoplace
298
299  else  ! tcpt     on reprend un fichier compteur (ICOMPTEUR.eq.1)
300
301     time=tbegin       ! prend le temps du compteur
302
303
304     call masque()
305     call flottab()
306     call neffect()
307     call flottab()
308     call masque()
309
310     do i=1,nx
311        do j=1,ny
312           if (S(i,j).lt.0) then
313              print*,i,j,S(i,j)
314              goto 11115
315           endif
316        enddo
317     enddo
31811115 continue
319
320     !       ========================================================
321     call flow_general
322
323     do iglen=n1poly,n2poly
324        call flowlaw(iglen)
325     end do
326
327
328     call Neffect()
329     call flottab
330     call diffusiv()
331     call SIA_velocities()
332     call strain_rate
333
334  endif tcpt
335  !     fin du test sur icompteur
336
337  !      call init_sortie_ncdf
338  !      call sortie_ncdf_cat
339
340  call flottab()
341  call Neffect()
342  call flottab()
343
344  if (icompteur.eq.0) then
345     do i=1,nx
346        do j=1,ny
347           if (.not.flot(i,j)) then
348              B(i,j) = Bsoc(i,j)
349              Uxbar(i,j) = 0.
350              Uybar(i,j) = 0.
351           end if
352        end do
353     end do
354  endif
355
356  boost = .false.
357
358  do i=2,nx-1
359     do j=2,ny-1
360        hwater(i,j)=max(hwater(i,j),0.)
361     enddo
362  enddo
363  timemax=time
364
365  ! sortie des champs initiaux
366
367  call testsort_time(tbegin)
368  call sortie_hz_multi   ! pour les variables declarees dans 3D
369!  call hz_output(tbegin)
370
371!  call limit_file(1,real(time),dt,tend,dtsortie,dtcpt,testdiag,dtt,runname)
372
373  isynchro=1
374  ndebug=0
375  ndebug_max=9
376
377  call step_thermomeca()     ! un tour dans la boucle temporelle, partie avant icethick
378  call init_sortie_ncdf
379  if (itracebug.eq.1)  call tracebug(' fin routine grisli_init')
380  call testsort_time_ncdf(dble(tbegin))
381
382  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
383
384  return
385end subroutine grisli_init
Note: See TracBrowser for help on using the repository browser.