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

Last change on this file since 254 was 244, checked in by aquiquet, 5 years ago

Grisli-iloveclim branch merged to trunk at revision 243

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
166  implicit none
167
168  if (itracebug.eq.1)  call tracebug(' Entree dans routine grisli_init')
169  !      switch pour passer ou non par T lliboutry calcule => 0, ne passe pas,
170  !      1 ou 2 passe (se met a 0 tout seul si on prend un fichier .cptr)
171
172  ITEMP=0
173
174  !      switch couple physique faible =>  CP et CT independant T
175  !               0     pas de trait. vert.  A FAIRE           niveau L0
176  !               1     pas de couplage , faible physique      niveau L1
177  !               2     couplage, faible physique              niveau L2
178  !               3     couplage, physique complete sans CBT   niveau L3
179  !               4     idem 3 mais loi de def. Duval          niveau L4
180  ICOUPLE=4
181  !     switch margin IMARGIN=0 fixed, IMARGIN=1 moving
182  IMARGIN=1
183
184  TIMECG=TBEGIN
185  nt=-1   ! utilisee dans initialisation flottab
186  !     sortie profile tous les dtprofile
187  DTPROFILE=50000.
188  marine=.true.
189  !     ----------------------------------fin des modifs run les plus usuelles
190  ! DIRNAMEOUT='./'
191  DIRNAMEOUT='outputdata/ism/'
192
193  call initial  ! routine qui appel toutes les routines d'initialisation
194
195
196  !      call init_sortie_ncdf
197  !      call sortie_ncdf_cat
198  !      STOP
199
200  !     compteur tous les DTCPT
201  DTCPT=dtout
202
203
204  !     ************ OPEN FILES.RITZ ****************
205
206  if ((geoplace.eq.'anteis1').or.(geoplace.eq.'ant20km')) then
207     ! fichier de reference pour le niveau des mers
208     open(num_sealevel,file=TRIM(DIRNAMEOUT)//'sealevel'//runname//'.ritz',position="append")
209     open(num_ts_ritz,file=TRIM(DIRNAMEOUT)//'ts_'//runname//'.ritz',position="append")
210     open(num_ic_vo,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'vo.ritz',position="append")
211     open(num_ic_by,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'by.ritz',position="append")
212     open(num_ic_dm,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dm.ritz',position="append")
213     open(num_ic_dc,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'dc.ritz',position="append")
214     open(num_ic_df,file=TRIM(DIRNAMEOUT)//'ic_'//runname//'df.ritz',position="append")
215  endif
216
217  !------------------------------ INITIALISATION ----------------------------
218  !
219! ecriture netcdf apres initialisation
220
221
222
223  call testsort_time_ncdf(dble(tbegin))
224  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
225
226
227!cdc supprime pour initialisation propre
228!~   if (iter_beta.eq.0) then
229
230!~      if (itracebug.eq.1)  call tracebug(' Avant appel routine icethick3')
231!~      call icethick3
232!~      debug_3D(:,:,88) = S(:,:)
233!~      if (itracebug.eq.1)  call tracebug(' Apres appel routine icethick3')
234!~   end if
235
236
237  !     Tgrounded, temps pendant lequel la calotte est terrestre
238  tgrounded=tbegin-10.
239  !if (tgrounded.le.tbegin) then
240  marine=.true. ! Cas la calotte est terrestre
241  !end if
242
243  ! test vincent car certains H(i,j)=0 dans fichier de reprise
244  do j=1,ny
245     do i=1,nx
246        H(i,j)=max(0.,H(i,j))
247     enddo
248  enddo
249
250
251  ! call firstoutput()           ! ouverture fichier temporel et premieres ecritures
252
253  call forclim                   !  initialisation BM et TS         
254  call ablation
255
256
257
258  !  -----------                  CALCULATION OF INITIAL TEMPERATURES
259
260  tcpt:if (ICOMPTEUR.eq.0) then
261
262
263     if ((GEOPLACE.ne.'eismint').and.(GEOPLACE(1:6).ne.'marine')) then
264        !       ITEMP=1 => calcul de T lliboutry; ITEMP=2 => reprise d'un fichier cptr
265        !       ITEMP=0 => on ne prend pas en compte T Lliboutry
266        !       ITEMP=3 => on prend les temperatures d'un fichier cptr
267
268
269
270        if ((ITEMP.eq.0).or.(ITEMP.eq.3)) then
271           call masque()
272
273           call Neffect()
274
275           call flottab()
276
277           call Neffect()
278
279
280           !          call vitbilan_lect   ! routine de lecture des vitesses de bilan
281           !       ========================================================
282
283           if (ITEMP.eq.0) call lineartemp()
284
285           call bmelt_grounded 
286           call  bmeltshelf
287
288
289           call flow_general
290
291           do iglen=n1poly,n2poly
292              call flowlaw(iglen)
293           end do
294
295           call Neffect()
296           call flottab()
297           call calving
298           call ablation_bord
299           call flottab
300           call Neffect()
301           call diffusiv()
302           call SIA_velocities()
303        endif
304
305
306     endif
307     !     fin du test geoplace
308
309  else  ! tcpt     on reprend un fichier compteur (ICOMPTEUR.eq.1)
310
311     time=tbegin       ! prend le temps du compteur
312
313
314     call masque()
315     call flottab()
316     call neffect()
317     call flottab()
318     call masque()
319
320     do i=1,nx
321        do j=1,ny
322           if (S(i,j).lt.0) then
323              print*,i,j,S(i,j)
324              goto 11115
325           endif
326        enddo
327     enddo
32811115 continue
329
330     call  bmeltshelf ! afq --
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  isynchro=1
377  ndebug=0
378  ndebug_max=9
379
380  call init_bilan_eau
381  call step_thermomeca()     ! un tour dans la boucle temporelle, partie avant icethick
382  call init_sortie_ncdf
383  if (itracebug.eq.1)  call tracebug(' fin routine grisli_init')
384  call testsort_time_ncdf(dble(tbegin))
385
386  if (iglob_ncdf .EQ. 1) call sortie_ncdf_cat
387
388  return
389end subroutine grisli_init
Note: See TracBrowser for help on using the repository browser.