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

Last change on this file since 198 was 198, checked in by aquiquet, 6 years ago

Grisli-iloveclim branch merged to trunk at revision 196

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