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

Last change on this file since 463 was 463, checked in by aquiquet, 5 months ago

Cleaning branch: masque subroutine with explicit arguments

File size: 10.6 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: itemp,icouple,isynchro,imargin,icompteur,iglen,timecg,marine,num_sealevel, &
134                          num_ts_ritz,num_ic_vo,num_ic_by,num_ic_dm,num_ic_dc,num_ic_df, &
135                          s,h,b,bsoc,flot,mk,mk0,uxbar,uybar,hwater,time,timemax,boost,ndebug,ndebug_max
136  use runparam, only: nt,tbegin,tgrounded,dtprofile,dtcpt,dirnameout,runname,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  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
190  !     ************ OPEN FILES.RITZ ****************
191
192  if ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
193     ! fichier de reference pour le niveau des mers
194     open(num_sealevel,file=TRIM(DIRNAMEOUT)//'sealevel'//runname//'.ritz',position="append")
195     open(num_ts_ritz,file=TRIM(DIRNAMEOUT)//'ts_'//runname//'.ritz',position="append")
196     open(num_ic_vo,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'vo.ritz',position="append")
197     open(num_ic_by,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'by.ritz',position="append")
198     open(num_ic_dm,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dm.ritz',position="append")
199     open(num_ic_dc,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dc.ritz',position="append")
200     open(num_ic_df,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'df.ritz',position="append")
201  endif
202
203  !------------------------------ INITIALISATION ----------------------------
204  !
205! ecriture netcdf apres initialisation
206
207
208
209  call testsort_time_ncdf(dble(tbegin))
210  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
211
212
213!cdc supprime pour initialisation propre
214!~   if (iter_beta.eq.0) then
215
216!~      if (itracebug.eq.1)  call tracebug(' Avant appel routine icethick3')
217!~      call icethick3
218!~      debug_3D(:,:,88) = S(:,:)
219!~      if (itracebug.eq.1)  call tracebug(' Apres appel routine icethick3')
220!~   end if
221
222
223  !     Tgrounded, temps pendant lequel la calotte est terrestre
224  tgrounded=tbegin-10.
225  !if (tgrounded.le.tbegin) then
226  marine=.true. ! Cas la calotte est terrestre
227  !end if
228
229  ! test vincent car certains H(i,j)=0 dans fichier de reprise
230  do j=1,ny
231     do i=1,nx
232        H(i,j)=max(0.,H(i,j))
233     enddo
234  enddo
235
236
237  ! call firstoutput()           ! ouverture fichier temporel et premieres ecritures
238
239  call forclim                   !  initialisation BM et TS         
240  call ablation
241
242
243
244  !  -----------                  CALCULATION OF INITIAL TEMPERATURES
245
246  tcpt:if (ICOMPTEUR.eq.0) then
247
248
249     if ((GEOPLACE.ne.'eismint').and.(GEOPLACE(1:6).ne.'marine')) then
250        !       ITEMP=1 => calcul de T lliboutry; ITEMP=2 => reprise d'un fichier cptr
251        !       ITEMP=0 => on ne prend pas en compte T Lliboutry
252        !       ITEMP=3 => on prend les temperatures d'un fichier cptr
253
254
255
256        if ((ITEMP.eq.0).or.(ITEMP.eq.3)) then
257           call masque(flot,mk,mk0,itracebug)
258
259           call Neffect()
260
261           call flottab()
262
263           call Neffect()
264
265
266           !          call vitbilan_lect   ! routine de lecture des vitesses de bilan
267           !       ========================================================
268
269           if (ITEMP.eq.0) call lineartemp()
270
271           call bmelt_grounded 
272           call  bmeltshelf
273
274
275           call flow_general
276
277           do iglen=n1poly,n2poly
278              call flowlaw(iglen)
279           end do
280
281           call Neffect()
282           call flottab()
283           call calving
284           call ablation_bord
285           call flottab
286           call Neffect()
287           call diffusiv()
288           call SIA_velocities()
289        endif
290
291
292     endif
293     !     fin du test geoplace
294
295  else  ! tcpt     on reprend un fichier compteur (ICOMPTEUR.eq.1)
296
297     time=tbegin       ! prend le temps du compteur
298
299
300     call masque(flot,mk,mk0,itracebug)
301     call flottab()
302     call neffect()
303     call flottab()
304     call masque(flot,mk,mk0,itracebug)
305
306     do i=1,nx
307        do j=1,ny
308           if (S(i,j).lt.0) then
309              print*,i,j,S(i,j)
310              goto 11115
311           endif
312        enddo
313     enddo
31411115 continue
315
316     call  bmeltshelf ! afq --
317
318     !       ========================================================
319     call flow_general
320
321     do iglen=n1poly,n2poly
322        call flowlaw(iglen)
323     end do
324
325
326     call Neffect()
327     call flottab
328     call diffusiv()
329     call SIA_velocities()
330     call strain_rate
331
332  endif tcpt
333  !     fin du test sur icompteur
334
335  !      call init_sortie_ncdf
336  !      call sortie_ncdf_cat
337
338  call flottab()
339  call Neffect()
340  call flottab()
341
342  if (icompteur.eq.0) then
343     do i=1,nx
344        do j=1,ny
345           if (.not.flot(i,j)) then
346              B(i,j) = Bsoc(i,j)
347              Uxbar(i,j) = 0.
348              Uybar(i,j) = 0.
349           end if
350        end do
351     end do
352  endif
353
354  boost = .false.
355
356  do i=2,nx-1
357     do j=2,ny-1
358        hwater(i,j)=max(hwater(i,j),0.)
359     enddo
360  enddo
361  timemax=time
362  isynchro=1
363  ndebug=0
364  ndebug_max=9
365
366  call init_bilan_eau
367  call step_thermomeca()     ! un tour dans la boucle temporelle, partie avant icethick
368  call init_sortie_ncdf
369  if (itracebug.eq.1)  call tracebug(' fin routine grisli_init')
370  call testsort_time_ncdf(dble(tbegin))
371
372  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
373
374  return
375end subroutine grisli_init
Note: See TracBrowser for help on using the repository browser.