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

Last change on this file since 40 was 40, checked in by roche, 8 years ago

Little tweaks for getting libgrisli without main program. Backported gfortran makefile changes into ifort makefile.

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