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

Last change on this file since 23 was 19, checked in by dumas, 9 years ago

climat-forcage-insolation_mod.f90 (Methode JB) validee avec fichier Ning, testsort_time avec passage de la variable time en double precision pour les sorties

File size: 10.3 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 interface_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 interface_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 interface_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
119  integer :: m
120
121  ! good luck
122
123  call grisli_init  ! Initializations
124
125  time_loop: do nt=1,ntmax         !____________________________ debut boucle temporelle
126
127     if (time.ge.tend) exit
128     if (time.gt.10) itracebug = 0
129     call step_time_loop()
130
131  end do time_loop
132  if (itracebug.eq.1)  call tracebug('dans main avant call out_recovery ')
133  call out_recovery(iout)
134
135  write(6,*) "end of the run at time = ",time
136  write(6,*) "_____________________________________________________________________"
137
138end program main3D
139
140
141!---------------------------------------------------------------------------------------
142subroutine grisli_init
143
144  USE module3D_phy
145  USE module_choix ! module de choix du type de run
146  !  module_choix donne acces a tous les modules
147  !  de declaration des packages
148  use flottab_mod
149  use interface_icetempmod
150  use sorties_ncdf_grisli
151  use util_recovery
152  use diagno_mod 
153!  use track_debug
154
155  implicit none
156
157  if (itracebug.eq.1)  call tracebug(' Entree dans routine grisli_init')
158  !      switch pour passer ou non par T lliboutry calcule => 0, ne passe pas,
159  !      1 ou 2 passe (se met a 0 tout seul si on prend un fichier .cptr)
160
161  ITEMP=0
162
163  !      switch couple physique faible =>  CP et CT independant T
164  !               0     pas de trait. vert.  A FAIRE           niveau L0
165  !               1     pas de couplage , faible physique      niveau L1
166  !               2     couplage, faible physique              niveau L2
167  !               3     couplage, physique complete sans CBT   niveau L3
168  !               4     idem 3 mais loi de def. Duval          niveau L4
169  ICOUPLE=4
170  !     switch margin IMARGIN=0 fixed, IMARGIN=1 moving
171  IMARGIN=1
172
173  TIMECG=TBEGIN
174  nt=-1   ! utilisee dans initialisation flottab
175  !     sortie profile tous les dtprofile
176  DTPROFILE=50000.
177  marine=.true.
178  !     ----------------------------------fin des modifs run les plus usuelles
179  ! DIRNAMEOUT='../RESULTATS/'
180  DIRNAMEOUT='./'
181
182  call initial  ! routine qui appel toutes les routines d'initialisation
183
184
185  !      call init_sortie_ncdf
186  !      call sortie_ncdf_cat
187  !      STOP
188
189  !     compteur tous les DTCPT
190  DTCPT=dtout
191
192  dtsortie=minval(dtsortie_hz(:))
193
194  !     ************ OPEN FILES.RITZ ****************
195
196  if ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
197     ! fichier de reference pour le niveau des mers
198     open(num_sealevel,file=TRIM(DIRNAMEOUT)//'sealevel'//runname//'.ritz',position="append")
199     open(num_ts_ritz,file=TRIM(DIRNAMEOUT)//'ts_'//runname//'.ritz',position="append")
200     open(num_ic_vo,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'vo.ritz',position="append")
201     open(num_ic_by,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'by.ritz',position="append")
202     open(num_ic_dm,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dm.ritz',position="append")
203     open(num_ic_dc,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dc.ritz',position="append")
204     open(num_ic_df,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'df.ritz',position="append")
205  endif
206
207  !------------------------------ INITIALISATION ----------------------------
208  !
209! ecriture netcdf apres initialisation
210
211
212
213  call testsort_time_ncdf(dble(tbegin))
214  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
215
216
217
218  if (iter_beta.eq.0) then
219
220     if (itracebug.eq.1)  call tracebug(' Avant appel routine icethick3')
221     call icethick3
222     debug_3D(:,:,88) = S(:,:)
223     if (itracebug.eq.1)  call tracebug(' Apres appel routine icethick3')
224  end if
225
226
227  !     Tgrounded, temps pendant lequel la calotte est terrestre
228  tgrounded=tbegin-10.
229  !if (tgrounded.le.tbegin) then
230  marine=.true. ! Cas la calotte est terrestre
231  !end if
232
233  ! test vincent car certains H(i,j)=0 dans fichier de reprise
234  do j=1,ny
235     do i=1,nx
236        H(i,j)=max(1.,H(i,j))
237     enddo
238  enddo
239
240
241  ! call firstoutput()           ! ouverture fichier temporel et premieres ecritures
242
243  call forclim                   !  initialisation BM et TS         
244  call ablation
245
246
247
248  !  -----------                  CALCULATION OF INITIAL TEMPERATURES
249
250  tcpt:if (ICOMPTEUR.eq.0) then
251
252
253     if ((GEOPLACE.ne.'eismint').and.(GEOPLACE(1:6).ne.'marine')) then
254        !       ITEMP=1 => calcul de T lliboutry; ITEMP=2 => reprise d'un fichier cptr
255        !       ITEMP=0 => on ne prend pas en compte T Lliboutry
256        !       ITEMP=3 => on prend les temperatures d'un fichier cptr
257
258
259
260        if ((ITEMP.eq.0).or.(ITEMP.eq.3)) then
261           call masque()
262
263           call Neffect()
264
265           call flottab()
266
267           call Neffect()
268
269
270           !          call vitbilan_lect   ! routine de lecture des vitesses de bilan
271           !       ========================================================
272
273           if (ITEMP.eq.0) call lineartemp()
274
275           call bmelt_grounded 
276           call  bmeltshelf
277
278
279           call flow_general
280
281           do iglen=n1poly,n2poly
282              call flowlaw(iglen)
283           end do
284
285
286           call Neffect()
287           call flottab()
288
289
290           call Neffect()
291
292
293           call diffusiv()
294           call SIA_velocities()
295
296        endif
297
298
299     endif
300     !     fin du test geoplace
301
302  else  ! tcpt     on reprend un fichier compteur (ICOMPTEUR.eq.1)
303
304     time=tbegin       ! prend le temps du compteur
305
306
307     call masque()
308     call flottab()
309     call neffect()
310     call flottab()
311     call masque()
312
313     do i=1,nx
314        do j=1,ny
315           if (S(i,j).lt.0) then
316              print*,i,j,S(i,j)
317              goto 11115
318           endif
319        enddo
320     enddo
32111115 continue
322
323     !       ========================================================
324     call flow_general
325
326     do iglen=n1poly,n2poly
327        call flowlaw(iglen)
328     end do
329
330
331     call Neffect()
332     call flottab
333     call diffusiv()
334     call SIA_velocities()
335     call strain_rate
336
337  endif tcpt
338  !     fin du test sur icompteur
339
340  !      call init_sortie_ncdf
341  !      call sortie_ncdf_cat
342
343  call flottab()
344  call Neffect()
345  call flottab()
346
347  if (icompteur.eq.0) then
348     do i=1,nx
349        do j=1,ny
350           if (.not.flot(i,j)) then
351              B(i,j) = Bsoc(i,j)
352              Uxbar(i,j) = 0.
353              Uybar(i,j) = 0.
354           end if
355        end do
356     end do
357  endif
358
359  boost = .false.
360
361  do i=2,nx-1
362     do j=2,ny-1
363        hwater(i,j)=max(hwater(i,j),0.)
364     enddo
365  enddo
366  timemax=time
367
368  ! sortie des champs initiaux
369
370  call testsort_time(tbegin)
371  call sortie_hz_multi   ! pour les variables declarees dans 3D
372!  call hz_output(tbegin)
373
374!  call limit_file(1,real(time),dt,tend,dtsortie,dtcpt,testdiag,dtt,runname)
375
376  isynchro=1
377  ndebug=0
378  ndebug_max=9
379
380  call step_thermomeca()     ! un tour dans la boucle temporelle, partie avant icethick
381  call init_sortie_ncdf
382  if (itracebug.eq.1)  call tracebug(' fin routine grisli_init')
383  call testsort_time_ncdf(dble(tbegin))
384
385  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
386
387  return
388end subroutine grisli_init
Note: See TracBrowser for help on using the repository browser.