source: branches/iLoveclim/SOURCES/main3D-0.4-40km.f90 @ 32

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

Recuperation des differences avec le code couplé iLOVECLIM. Makefile et programme principale ne sont pas encore adaptés

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