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

Last change on this file since 91 was 91, checked in by aquiquet, 8 years ago

GRISLI coupled using basal melting rates coming from CLIO. Might need further testing for LGM conditions.

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