source: branches/GRISLIv3/SOURCES/main3D-0.4-40km.f90 @ 483

Last change on this file since 483 was 481, checked in by aquiquet, 4 months ago

Cleaning branch: unused variables removed following strict compilation

File size: 8.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 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, only: time,iout,ntmax
105  use runparam, only: tend,itracebug,nt
106
107  implicit none
108
109
110  ! good luck
111
112  call grisli_init  ! Initializations
113
114  time_loop: do nt=1,ntmax         !____________________________ debut boucle temporelle
115
116     if (time.ge.tend) exit
117     if (time.gt.10) itracebug = 0
118     call step_time_loop()
119
120  end do time_loop
121  if (itracebug.eq.1)  call tracebug('dans main avant call out_recovery ')
122  call out_recovery(iout)
123
124  write(6,*) "end of the run at time = ",time
125  write(6,*) "_____________________________________________________________________"
126
127end program main3D
128
129
130!---------------------------------------------------------------------------------------
131subroutine grisli_init
132
133  USE module3D_phy, only: isynchro,icompteur,iglen, &
134                          ice,bm,bmelt,ablbord,ablbord_dtt,dt,    &
135                          s,h,b,bsoc,flot,mk,mk0,uxbar,uybar,hwater,time,timemax,ndebug,ndebug_max
136  use runparam, only: nt,tbegin,dtprofile,dtcpt,dirnameout,itracebug
137  use geography, only: nx,ny,geoplace
138  use deformation_mod_2lois, only:n1poly,n2poly
139  use bilan_eau_mod, only: init_bilan_eau
140  use module_choix, only: forclim,ablation,bmeltshelf,calving,flow_general,flowlaw
141  !  module_choix donne acces a tous les modules
142  !  de declaration des packages
143  use flottab_mod, only: flottab
144  use sorties_ncdf_grisli, only: iglob_ncdf,testsort_time_ncdf,init_sortie_ncdf,testsort_time_ncdf, &
145                                 sortie_ncdf_cat
146  use util_recovery, only: dtout
147 
148!  use track_debug
149
150  implicit none
151
152  integer :: i,j
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  nt=-1   ! utilisee dans initialisation flottab
159  !     sortie profile tous les dtprofile
160  DTPROFILE=50000.
161  !     ----------------------------------fin des modifs run les plus usuelles
162  DIRNAMEOUT='../RESULTATS/'
163  !DIRNAMEOUT='./'
164
165  call initial  ! routine qui appel toutes les routines d'initialisation
166
167
168  !      call init_sortie_ncdf
169  !      call sortie_ncdf_cat
170  !      STOP
171
172  !     compteur tous les DTCPT
173  DTCPT=dtout
174
175  !------------------------------ INITIALISATION ----------------------------
176  !
177! ecriture netcdf apres initialisation
178
179
180
181  call testsort_time_ncdf(dble(tbegin))
182  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
183
184  ! test vincent car certains H(i,j)=0 dans fichier de reprise
185  do j=1,ny
186     do i=1,nx
187        H(i,j)=max(0.,H(i,j))
188     enddo
189  enddo
190
191
192  call forclim                   !  initialisation BM et TS         
193  call ablation
194
195
196
197  !  -----------                  CALCULATION OF INITIAL TEMPERATURES
198
199  tcpt:if (ICOMPTEUR.eq.0) then
200
201           call masque(flot,mk,mk0,itracebug)
202
203           call Neffect()
204
205           call flottab()
206
207           call Neffect()
208
209
210           !          call vitbilan_lect   ! routine de lecture des vitesses de bilan
211           !       ========================================================
212
213           call lineartemp()
214
215           call bmelt_grounded 
216           call  bmeltshelf
217
218
219           call flow_general
220
221           do iglen=n1poly,n2poly
222              call flowlaw(iglen)
223           end do
224
225           call Neffect()
226           call flottab()
227           call calving
228           call ablation_bord(ice,bm,bmelt,ablbord,ablbord_dtt,dt)
229           call flottab
230           call Neffect()
231           call diffusiv()
232           call SIA_velocities()
233
234  else  ! tcpt     on reprend un fichier compteur (ICOMPTEUR.eq.1)
235
236     time=tbegin       ! prend le temps du compteur
237
238
239     call masque(flot,mk,mk0,itracebug)
240     call flottab()
241     call neffect()
242     call flottab()
243     call masque(flot,mk,mk0,itracebug)
244
245     do i=1,nx
246        do j=1,ny
247           if (S(i,j).lt.0) then
248              print*,i,j,S(i,j)
249              goto 11115
250           endif
251        enddo
252     enddo
25311115 continue
254
255     call  bmeltshelf ! afq --
256
257     !       ========================================================
258     call flow_general
259
260     do iglen=n1poly,n2poly
261        call flowlaw(iglen)
262     end do
263
264
265     call Neffect()
266     call flottab
267     call diffusiv()
268     call SIA_velocities()
269     call strain_rate
270
271  endif tcpt
272  !     fin du test sur icompteur
273
274  !      call init_sortie_ncdf
275  !      call sortie_ncdf_cat
276
277  call flottab()
278  call Neffect()
279  call flottab()
280
281  if (icompteur.eq.0) then
282     do i=1,nx
283        do j=1,ny
284           if (.not.flot(i,j)) then
285              B(i,j) = Bsoc(i,j)
286              Uxbar(i,j) = 0.
287              Uybar(i,j) = 0.
288           end if
289        end do
290     end do
291  endif
292
293  do i=2,nx-1
294     do j=2,ny-1
295        hwater(i,j)=max(hwater(i,j),0.)
296     enddo
297  enddo
298  timemax=time
299  isynchro=1
300  ndebug=0
301  ndebug_max=9
302
303  call init_bilan_eau
304  call step_thermomeca()     ! un tour dans la boucle temporelle, partie avant icethick
305  call init_sortie_ncdf
306  if (itracebug.eq.1)  call tracebug(' fin routine grisli_init')
307  call testsort_time_ncdf(dble(tbegin))
308
309  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
310
311  return
312end subroutine grisli_init
Note: See TracBrowser for help on using the repository browser.